Skip to content

Commit

Permalink
set diag_init_time correctly to the base_date, fix line length limit
Browse files Browse the repository at this point in the history
  • Loading branch information
uramirez8707 committed Jun 3, 2024
1 parent 91a45f5 commit e8c20c2
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 12 deletions.
2 changes: 1 addition & 1 deletion diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4210,7 +4210,7 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
END IF

if (use_modern_diag) then
CALL fms_diag_object%init(diag_subset_output)
CALL fms_diag_object%init(diag_subset_output, time_init)
endif
if (.not. use_modern_diag) then
CALL parse_diag_table(DIAG_SUBSET=diag_subset_output, ISTAT=mystat, ERR_MSG=err_msg_local)
Expand Down
16 changes: 8 additions & 8 deletions diag_manager/fms_diag_file_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -264,8 +264,8 @@ logical function fms_diag_files_object_init (files_array)
!! This will be the base_time if nothing was passed in
!! This time is appended to the filename if the prepend_date namelist is .True.
obj%start_time = diag_init_time
obj%last_output = get_base_time()
obj%model_time = get_base_time()
obj%last_output = diag_init_time
obj%model_time = diag_init_time
obj%next_output = diag_time_inc(obj%start_time, obj%get_file_freq(), obj%get_file_frequnit())
obj%next_next_output = diag_time_inc(obj%next_output, obj%get_file_freq(), obj%get_file_frequnit())

Expand Down Expand Up @@ -1009,18 +1009,18 @@ subroutine add_start_time(this, start_time)
class(fmsDiagFile_type), intent(inout) :: this !< The file object
TYPE(time_type), intent(in) :: start_time !< Start time to add to the fileobj

!< If the start_time sent in is equal to the base_time return because
!! this%start_time was already set to the base_time
if (start_time .eq. get_base_time()) return
!< If the start_time sent in is equal to the diag_init_time return because
!! this%start_time was already set to the diag_init_time
if (start_time .eq. diag_init_time) return

if (this%start_time .ne. get_base_time()) then
!> If the this%start_time is not equal to the base_time from the diag_table
if (this%start_time .ne. diag_init_time) then
!> If the this%start_time is not equal to the diag_init_time from the diag_table
!! this%start_time was already updated so make sure it is the same or error out
if (this%start_time .ne. start_time)&
call mpp_error(FATAL, "The variables associated with the file:"//this%get_file_fname()//" have"&
&" different start_time")
else
!> If the this%start_time is equal to the base_time,
!> If the this%start_time is equal to the diag_init_time,
!! simply update it with the start_time and set up the *_output variables
this%model_time = start_time
this%start_time = start_time
Expand Down
13 changes: 11 additions & 2 deletions diag_manager/fms_diag_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module fms_diag_object_mod
&DIAG_FIELD_NOT_FOUND, diag_not_registered, max_axes, TWO_D_DOMAIN, &
&get_base_time, NULL_AXIS_ID, get_var_type, diag_not_registered, &
&time_none, time_max, time_min, time_sum, time_average, time_diurnal, &
&time_power, time_rms, r8, NO_DOMAIN
&time_power, time_rms, r8, NO_DOMAIN, diag_init_time

USE time_manager_mod, ONLY: set_time, set_date, get_time, time_type, OPERATOR(>=), OPERATOR(>),&
& OPERATOR(<), OPERATOR(==), OPERATOR(/=), OPERATOR(/), OPERATOR(+), ASSIGNMENT(=), get_date, &
Expand Down Expand Up @@ -118,14 +118,23 @@ module fms_diag_object_mod
!! Reads the diag_table.yaml and fills in the yaml object
!! Allocates the diag manager object arrays for files, fields, and buffers
!! Initializes variables
subroutine fms_diag_object_init (this,diag_subset_output)
subroutine fms_diag_object_init (this,diag_subset_output, time_init)
class(fmsDiagObject_type) :: this !< Diag mediator/controller object
integer :: diag_subset_output !< Subset of the diag output?
INTEGER, DIMENSION(6), OPTIONAL, INTENT(IN) :: time_init !< Model time diag_manager initialized

#ifdef use_yaml
if (this%initialized) return

! allocate(diag_objs(get_num_unique_fields()))
CALL diag_yaml_object_init(diag_subset_output)

!! Doing this here, because the base_time is not set until the yaml is parsed
!! if time_init is present, it will be set in diag_manager_init
if (.not. present(time_init)) then
diag_init_time = get_base_time()
endif

this%axes_initialized = fms_diag_axis_object_init(this%diag_axis)
this%files_initialized = fms_diag_files_object_init(this%FMS_diag_files)
this%fields_initialized = fms_diag_fields_object_init(this%FMS_diag_fields)
Expand Down
3 changes: 2 additions & 1 deletion test_fms/diag_manager/test_prepend_date.F90
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,8 @@ subroutine check_output()
call mpp_error(FATAL, "Error opening file:00020101.test_static.nc to read")

call read_data(fileobj, "var2", var_data(1))
if (var_data(1) .ne. real(123.456, kind=r4_kind)) call mpp_error(FATAL, "The variable data for var2 is not the correct value!")
if (var_data(1) .ne. real(123.456, kind=r4_kind)) call mpp_error(FATAL, &
"The variable data for var2 is not the correct value!")

call close_file(fileobj)

Expand Down

0 comments on commit e8c20c2

Please sign in to comment.