Skip to content

Commit

Permalink
Add capability to time diag manager
Browse files Browse the repository at this point in the history
  • Loading branch information
uramirez8707 committed May 17, 2024
1 parent 98e2ebd commit 8e5ad93
Show file tree
Hide file tree
Showing 3 changed files with 115 additions and 4 deletions.
5 changes: 4 additions & 1 deletion diag_manager/diag_axis.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ MODULE diag_axis_mod
& fms_error_handler, FATAL, NOTE
USE diag_data_mod, ONLY: diag_axis_type, max_subaxes, max_axes,&
& max_num_axis_sets, max_axis_attributes, debug_diag_manager,&
& first_send_data_call, diag_atttype, use_modern_diag
& first_send_data_call, diag_atttype, use_modern_diag, diag_manger_clock
use fms_diag_object_mod, only:fms_diag_object
USE netcdf, ONLY: NF90_INT, NF90_FLOAT, NF90_CHAR

Expand Down Expand Up @@ -131,6 +131,7 @@ INTEGER FUNCTION diag_axis_init(name, array_data, units, cart_name, long_name, d
INTEGER :: isc, iec, isg, ieg
CHARACTER(len=128) :: emsg

call diag_manger_clock%start_register_axis_clock()
IF ( .NOT.module_is_initialized ) THEN
CALL write_version_number("DIAG_AXIS_MOD", version)
ENDIF
Expand All @@ -141,6 +142,7 @@ INTEGER FUNCTION diag_axis_init(name, array_data, units, cart_name, long_name, d
diag_axis_init = fms_diag_object%fms_diag_axis_init(name, array_data, units, cart_name, size(array_data(:)), &
& long_name=long_name, direction=direction, set_name=set_name, edges=edges, Domain=Domain, Domain2=Domain2, &
& DomainU=DomainU, aux=aux, req=req, tile_count=tile_count, domain_position=domain_position)
call diag_manger_clock%end_register_axis_clock()
return
endif
IF ( PRESENT(tile_count)) THEN
Expand Down Expand Up @@ -367,6 +369,7 @@ INTEGER FUNCTION diag_axis_init(name, array_data, units, cart_name, long_name, d

! Module is now initialized
module_is_initialized = .TRUE.
call diag_manger_clock%end_register_axis_clock()

END FUNCTION diag_axis_init

Expand Down
96 changes: 96 additions & 0 deletions diag_manager/diag_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ MODULE diag_data_mod
USE fms_mod, ONLY: write_version_number
USE fms_diag_bbox_mod, ONLY: fmsDiagIbounds_type
use mpp_mod, ONLY: mpp_error, FATAL, WARNING, mpp_pe, mpp_root_pe, stdlog
use mpp_mod, ONLY: mpp_clock_begin, mpp_clock_id, mpp_clock_end

! NF90_FILL_REAL has value of 9.9692099683868690e+36.
USE netcdf, ONLY: NF_FILL_REAL => NF90_FILL_REAL
Expand Down Expand Up @@ -131,6 +132,29 @@ MODULE diag_data_mod
INTEGER, PARAMETER :: is_y_axis = 2 !< integer indicating that it is a y axis
!> @}

TYPE :: diagManagerClock_type
integer :: register_axis_clock
integer :: register_field_clock
integer :: send_data_clock
integer :: diag_send_complete_clock
integer :: diag_manager_end_clock

contains
procedure :: init_clocks
procedure :: start_register_axis_clock
procedure :: start_register_field_clock
procedure :: start_send_data_clock
procedure :: start_diag_send_complete_clock
procedure :: start_diag_manager_end_clock
procedure :: end_register_axis_clock
procedure :: end_register_field_clock
procedure :: end_send_data_clock
procedure :: end_diag_send_complete_clock
procedure :: end_diag_manager_end_clock
END TYPE diagManagerClock_type

type(diagManagerClock_type) :: diag_manger_clock

!> @brief Contains the coordinates of the local domain to output.
!> @ingroup diag_data_mod
TYPE diag_grid
Expand Down Expand Up @@ -388,6 +412,7 @@ MODULE diag_data_mod
!! routine is called with the optional time_init parameter.
LOGICAL :: use_mpp_io = .false. !< false is fms2_io (default); true is mpp_io
LOGICAL :: use_refactored_send = .false. !< Namelist flag to use refactored send_data math funcitons.
LOGICAL :: timed_diag_manager = .false.
LOGICAL :: use_modern_diag = .false. !< Namelist flag to use the modernized diag_manager code
LOGICAL :: use_clock_average = .false. !< .TRUE. if the averaging of variable is done based on the clock
!! For example, if doing daily averages and your start the simulation in
Expand Down Expand Up @@ -647,6 +672,77 @@ subroutine write_metadata(this, fileobj, var_name, cell_methods)
end select

end subroutine write_metadata

subroutine init_clocks(this)
class(diagManagerClock_type), intent(inout) :: this

if (.not. timed_diag_manager) return
this%register_axis_clock = mpp_clock_id("register_axis_clock")
this%register_field_clock = mpp_clock_id("register_field_clock")
this%send_data_clock = mpp_clock_id("send_data_clock")
this%diag_send_complete_clock = mpp_clock_id("diag_send_complete_clock")
this%diag_manager_end_clock = mpp_clock_id("diag_manager_end_clock")
end subroutine init_clocks

subroutine start_register_axis_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_begin(this%register_axis_clock)
end subroutine start_register_axis_clock

subroutine start_register_field_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_begin(this%register_field_clock)
end subroutine start_register_field_clock

subroutine start_send_data_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_begin(this%send_data_clock)
end subroutine start_send_data_clock

subroutine start_diag_send_complete_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_begin(this%diag_send_complete_clock)
end subroutine start_diag_send_complete_clock

subroutine start_diag_manager_end_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_begin(this%diag_manager_end_clock)
end subroutine start_diag_manager_end_clock

subroutine end_register_axis_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_end(this%register_axis_clock)
end subroutine end_register_axis_clock

subroutine end_register_field_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_end(this%register_field_clock)
end subroutine end_register_field_clock

subroutine end_send_data_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_end(this%send_data_clock)
end subroutine end_send_data_clock

subroutine end_diag_send_complete_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_end(this%diag_send_complete_clock)
end subroutine end_diag_send_complete_clock

subroutine end_diag_manager_end_clock(this)
class(diagManagerClock_type), intent(inout) :: this
if (.not. timed_diag_manager) return
call mpp_clock_end(this%diag_manager_end_clock)
end subroutine end_diag_manager_end_clock
END MODULE diag_data_mod
!> @}
! close documentation grouping
18 changes: 15 additions & 3 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -234,8 +234,8 @@ MODULE diag_manager_mod
& use_cmor, issue_oor_warnings, oor_warnings_fatal, oor_warning, pack_size,&
& max_out_per_in_field, flush_nc_files, region_out_use_alt_value, max_field_attributes, output_field_type,&
& max_file_attributes, max_axis_attributes, prepend_date, DIAG_FIELD_NOT_FOUND, diag_init_time, diag_data_init,&
& use_mpp_io, use_refactored_send, &
& use_modern_diag, use_clock_average, diag_null, pack_size_str
& use_mpp_io, use_refactored_send, timed_diag_manager, &
& use_modern_diag, use_clock_average, diag_null, pack_size_str, diag_manger_clock
USE diag_data_mod, ONLY: fileobj, fileobjU, fnum_for_domain, fileobjND
USE diag_table_mod, ONLY: parse_diag_table
USE diag_output_mod, ONLY: get_diag_global_att, set_diag_global_att
Expand Down Expand Up @@ -408,6 +408,7 @@ INTEGER FUNCTION register_diag_field_scalar(module_name, field_name, init_time,
END IF
END IF
if (use_modern_diag) then
call diag_manger_clock%start_register_field_clock()
if( do_diag_field_log) then
if ( PRESENT(do_not_log) ) THEN
if(.not. do_not_log) call log_diag_field_info(module_name, field_name, (/NULL_AXIS_ID/), long_name,&
Expand All @@ -422,6 +423,7 @@ INTEGER FUNCTION register_diag_field_scalar(module_name, field_name, init_time,
& missing_value=missing_value, var_range=range, standard_name=standard_name, &
& do_not_log=do_not_log, err_msg=err_msg, area=area, volume=volume, realm=realm, &
multiple_send_data=multiple_send_data)
call diag_manger_clock%end_register_field_clock()
else
register_diag_field_scalar = register_diag_field_scalar_old(module_name, field_name, init_time, &
& long_name=long_name, units=units, missing_value=missing_value, range=range, standard_name=standard_name, &
Expand Down Expand Up @@ -458,6 +460,7 @@ INTEGER FUNCTION register_diag_field_array(module_name, field_name, axes, init_t
LOGICAL, OPTIONAL, INTENT(in) :: multiple_send_data !< .True. if send data is called, multiple times
!! for the same time

call diag_manger_clock%start_register_field_clock()
if (use_modern_diag) then
if( do_diag_field_log) then
if ( PRESENT(do_not_log) ) THEN
Expand All @@ -480,6 +483,7 @@ INTEGER FUNCTION register_diag_field_array(module_name, field_name, axes, init_t
& standard_name=standard_name, verbose=verbose, do_not_log=do_not_log, err_msg=err_msg, &
& interp_method=interp_method, tile_count=tile_count, area=area, volume=volume, realm=realm)
endif
call diag_manger_clock%end_register_field_clock()
end function register_diag_field_array

!> @brief Return field index for subsequent call to send_data.
Expand Down Expand Up @@ -1665,6 +1669,7 @@ LOGICAL FUNCTION send_data_3d(diag_field_id, field, time, is_in, js_in, ks_in, &
CLASS(*), DIMENSION(:,:,:), INTENT(in), OPTIONAL :: rmask
CHARACTER(len=*), INTENT(out), OPTIONAL :: err_msg

call diag_manger_clock%start_send_data_clock()
if (present(mask) .and. present(rmask)) then
send_data_3d = diag_send_data(diag_field_id, field, time=time, is_in=is_in, js_in=js_in, ks_in=ks_in, &
mask=mask, rmask=rmask, ie_in=ie_in, je_in=je_in, ke_in=ke_in, weight=weight, &
Expand All @@ -1679,6 +1684,7 @@ LOGICAL FUNCTION send_data_3d(diag_field_id, field, time, is_in, js_in, ks_in, &
send_data_3d = diag_send_data(diag_field_id, field, time=time, is_in=is_in, js_in=js_in, ks_in=ks_in, &
ie_in=ie_in, je_in=je_in, ke_in=ke_in, weight=weight, err_msg=err_msg)
endif
call diag_manger_clock%end_send_data_clock()
END FUNCTION send_data_3d

!> @return true if send is successful
Expand Down Expand Up @@ -3906,6 +3912,7 @@ SUBROUTINE diag_send_complete(time_step, err_msg)
logical :: local_output, need_compute
CHARACTER(len=128) :: error_string

call diag_manger_clock%start_diag_send_complete_clock()
IF ( Time_end == Time_zero ) THEN
! <ERROR STATUS="FATAL">
! diag_manager_set_time_end must be called before diag_send_complete
Expand All @@ -3916,6 +3923,7 @@ SUBROUTINE diag_send_complete(time_step, err_msg)

if (use_modern_diag) then
call fms_diag_object%fms_diag_send_complete(time_step)
call diag_manger_clock%end_diag_send_complete_clock()
return
endif

Expand Down Expand Up @@ -3962,6 +3970,7 @@ SUBROUTINE diag_send_complete(time_step, err_msg)
END DO
END DO

call diag_manger_clock%end_diag_send_complete_clock()
END SUBROUTINE diag_send_complete

!> @brief Flushes diagnostic buffers where necessary. Close diagnostics files.
Expand All @@ -3971,6 +3980,7 @@ SUBROUTINE diag_manager_end(time)

INTEGER :: file

call diag_manger_clock%start_diag_manager_end_clock()
IF ( do_diag_field_log ) THEN
close (diag_log_unit)
END IF
Expand All @@ -3985,6 +3995,7 @@ SUBROUTINE diag_manager_end(time)
if (use_modern_diag) then
call fms_diag_object%diag_end(time)
endif
call diag_manger_clock%end_diag_manager_end_clock()
END SUBROUTINE diag_manager_end

!> @brief Replaces diag_manager_end; close just one file: files(file)
Expand Down Expand Up @@ -4084,7 +4095,7 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
& max_num_axis_sets, max_files, use_cmor, issue_oor_warnings,&
& oor_warnings_fatal, max_out_per_in_field, flush_nc_files, region_out_use_alt_value, max_field_attributes,&
& max_file_attributes, max_axis_attributes, prepend_date, use_modern_diag, use_clock_average, &
& field_log_separator, use_refactored_send
& field_log_separator, use_refactored_send, timed_diag_manager

! If the module was already initialized do nothing
IF ( module_is_initialized ) RETURN
Expand Down Expand Up @@ -4209,6 +4220,7 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
END IF
END IF

call diag_manger_clock%init_clocks()
if (use_modern_diag) then
CALL fms_diag_object%init(diag_subset_output)
endif
Expand Down

0 comments on commit 8e5ad93

Please sign in to comment.