Skip to content

Commit

Permalink
fix: modern_diag_manager use the correct date in file name for static…
Browse files Browse the repository at this point in the history
… files (#1540)
  • Loading branch information
uramirez8707 authored Jun 14, 2024
1 parent 5757c78 commit b554b32
Show file tree
Hide file tree
Showing 6 changed files with 244 additions and 18 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
29 changes: 17 additions & 12 deletions diag_manager/fms_diag_file_object.F90
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ module fms_diag_file_object_mod
get_base_second, time_unit_list, time_average, time_rms, time_max, time_min, time_sum, &
time_diurnal, time_power, time_none, avg_name, no_units, pack_size_str, &
middle_time, begin_time, end_time, MAX_STR_LEN, index_gridtype, latlon_gridtype, &
null_gridtype, flush_nc_files
null_gridtype, flush_nc_files, diag_init_time
use time_manager_mod, only: time_type, operator(>), operator(/=), operator(==), get_date, get_calendar_type, &
VALID_CALENDAR_TYPES, operator(>=), date_to_string, &
OPERATOR(/), OPERATOR(+), operator(<)
Expand Down Expand Up @@ -259,9 +259,13 @@ logical function fms_diag_files_object_init (files_array)

!> Set the start_time of the file to the base_time and set up the *_output variables
obj%done_writing_data = .false.
obj%start_time = get_base_time()
obj%last_output = get_base_time()
obj%model_time = get_base_time()

!! Set this to the time passed in to diag_manager_init
!! 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 = 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 @@ -1003,20 +1007,21 @@ end subroutine define_new_subaxis
!! So it needs to make sure that the start_time is the same for each variable. The initial value is the base_time
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
TYPE(time_type), intent(in) :: start_time !< Start time passed into register_diag_field

!< 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
!! this%start_time was already updated so make sure it is the same or error out
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 for the current variable
!! 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
7 changes: 4 additions & 3 deletions test_fms/diag_manager/Makefile.am
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ check_PROGRAMS = test_diag_manager test_diag_manager_time \
check_time_min check_time_max check_time_sum check_time_avg test_diag_diurnal check_time_diurnal \
check_time_pow check_time_rms check_subregional test_cell_measures test_var_masks \
check_var_masks test_multiple_send_data test_diag_out_yaml test_output_every_freq \
test_dm_weights
test_dm_weights test_prepend_date

# This is the source code for the test.
test_output_every_freq_SOURCES = test_output_every_freq.F90
Expand Down Expand Up @@ -64,6 +64,7 @@ check_subregional_SOURCES = check_subregional.F90
test_var_masks_SOURCES = test_var_masks.F90
check_var_masks_SOURCES = check_var_masks.F90
test_multiple_send_data_SOURCES = test_multiple_send_data.F90
test_prepend_date_SOURCES = test_prepend_date.F90

TEST_EXTENSIONS = .sh
SH_LOG_DRIVER = env AM_TAP_AWK='$(AWK)' $(SHELL) \
Expand All @@ -73,15 +74,15 @@ SH_LOG_DRIVER = env AM_TAP_AWK='$(AWK)' $(SHELL) \
TESTS = test_diag_manager2.sh test_time_none.sh test_time_min.sh test_time_max.sh test_time_sum.sh \
test_time_avg.sh test_time_pow.sh test_time_rms.sh test_time_diurnal.sh test_cell_measures.sh \
test_subregional.sh test_var_masks.sh test_multiple_send_data.sh test_output_every_freq.sh \
test_dm_weights.sh test_flush_nc_file.sh
test_dm_weights.sh test_flush_nc_file.sh test_prepend_date.sh

testing_utils.mod: testing_utils.$(OBJEXT)

# Copy over other needed files to the srcdir
EXTRA_DIST = test_diag_manager2.sh check_crashes.sh test_time_none.sh test_time_min.sh test_time_max.sh \
test_time_sum.sh test_time_avg.sh test_time_pow.sh test_time_rms.sh test_time_diurnal.sh \
test_cell_measures.sh test_subregional.sh test_var_masks.sh test_multiple_send_data.sh \
test_flush_nc_file.sh test_dm_weights.sh test_output_every_freq.sh
test_flush_nc_file.sh test_dm_weights.sh test_output_every_freq.sh test_prepend_date.sh

if USING_YAML
skipflag=""
Expand Down
124 changes: 124 additions & 0 deletions test_fms/diag_manager/test_prepend_date.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,124 @@
!***********************************************************************
!* GNU Lesser General Public License
!*
!* This file is part of the GFDL Flexible Modeling System (FMS).
!*
!* FMS is free software: you can redistribute it and/or modify it under
!* the terms of the GNU Lesser General Public License as published by
!* the Free Software Foundation, either version 3 of the License, or (at
!* your option) any later version.
!*
!* FMS is distributed in the hope that it will be useful, but WITHOUT
!* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
!* FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
!* for more details.
!*
!* You should have received a copy of the GNU Lesser General Public
!* License along with FMS. If not, see <http://www.gnu.org/licenses/>.
!***********************************************************************

!> @brief This programs tests diag manager when the init date is prepended to the file name
program test_prepend_date

use fms_mod, only: fms_init, fms_end, string
use diag_manager_mod, only: diag_axis_init, send_data, diag_send_complete, diag_manager_set_time_end, &
register_diag_field, diag_manager_init, diag_manager_end, register_static_field, &
diag_axis_init
use time_manager_mod, only: time_type, operator(+), JULIAN, set_time, set_calendar_type, set_date
use mpp_mod, only: FATAL, mpp_error, input_nml_file
use fms2_io_mod, only: FmsNetcdfFile_t, open_file, close_file, read_data, get_dimension_size
use platform_mod, only: r4_kind

implicit none

integer :: id_var0, id_var2, id_var1 !< diag field ids
integer :: id_axis1 !< Id for axis
logical :: used !< for send_data calls
integer :: ntimes = 48 !< Number of time steps
real :: vdata !< Buffer to store the data
type(time_type) :: Time !< "Model" time
type(time_type) :: Time_step !< Time step for the "simulation"
integer :: i !< For do loops
logical :: pass_diag_time = .True. !< .True. if passing the time to diag_manager_init

integer :: io_status !< Status when reading the namelist

namelist / test_prepend_date_nml / pass_diag_time

call fms_init

read (input_nml_file, test_prepend_date_nml, iostat=io_status)
if (io_status > 0) call mpp_error(FATAL,'=>test_prepend_date: Error reading input.nml')

call set_calendar_type(JULIAN)

! This is going to be different from the base_date
if (pass_diag_time) then
call diag_manager_init(time_init=(/2, 1, 1, 0, 0, 0/))
else
call diag_manager_init()
endif

Time = set_date(2,1,1,0,0,0)
Time_step = set_time (3600,0) !< 1 hour
call diag_manager_set_time_end(set_date(2,1,3,0,0,0))

id_axis1 = diag_axis_init('dummy_axis', (/real(1.)/), "mullions", "X")
id_var0 = register_diag_field ('ocn_mod', 'var0', Time)
id_var2 = register_static_field ('ocn_mod', 'var2', (/id_axis1/))

! This is a different start_time, should lead to a crash if the variable is in the diag table yaml
id_var1 = register_diag_field ('ocn_mod', 'var1', set_date(2,1,6,0,0,0))

used = send_data(id_var2, real(123.456))
do i = 1, ntimes
Time = Time + Time_step
vdata = real(i)

used = send_data(id_var0, vdata, Time) !< Sending data every hour!

call diag_send_complete(Time_step)
enddo

call diag_manager_end(Time)

call check_output()
call fms_end

contains

!< @brief Check the diag manager output
subroutine check_output()
type(FmsNetcdfFile_t) :: fileobj !< Fms2io fileobj
integer :: var_size !< Size of the variable reading
real(kind=r4_kind), allocatable :: var_data(:) !< Buffer to read variable data to
integer :: j !< For looping

if (.not. open_file(fileobj, "00020101.test_non_static.nc", "read")) &
call mpp_error(FATAL, "Error opening file:00020101.test_non_static.nc to read")

call get_dimension_size(fileobj, "time", var_size)
if (var_size .ne. 48) call mpp_error(FATAL, "The dimension of time in the file:test_0days is not the "//&
"correct size!")
allocate(var_data(var_size))
var_data = -999.99

call read_data(fileobj, "var0", var_data)
do j = 1, var_size
if (var_data(j) .ne. real(j, kind=r4_kind)) call mpp_error(FATAL, "The variable data for var1 at time level:"//&
string(j)//" is not the correct value!")
enddo

call close_file(fileobj)

if (.not. open_file(fileobj, "00020101.test_static.nc", "read")) &
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!")

call close_file(fileobj)

end subroutine check_output
end program test_prepend_date
87 changes: 87 additions & 0 deletions test_fms/diag_manager/test_prepend_date.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,87 @@
#!/bin/sh

#***********************************************************************
#* GNU Lesser General Public License
#*
#* This file is part of the GFDL Flexible Modeling System (FMS).
#*
#* FMS is free software: you can redistribute it and/or modify it under
#* the terms of the GNU Lesser General Public License as published by
#* the Free Software Foundation, either version 3 of the License, or (at
#* your option) any later version.
#*
#* FMS is distributed in the hope that it will be useful, but WITHOUT
#* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
#* FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
#* for more details.
#*
#* You should have received a copy of the GNU Lesser General Public
#* License along with FMS. If not, see <http://www.gnu.org/licenses/>.
#***********************************************************************

# Set common test settings.
. ../test-lib.sh

if [ -z "${skipflag}" ]; then
# create and enter directory for in/output files
output_dir

cat <<_EOF > diag_table.yaml
title: test_prepend_date
base_date: 1 1 1 0 0 0
diag_files:
- file_name: test_non_static
time_units: hours
unlimdim: time
freq: 1 hours
varlist:
- module: ocn_mod
var_name: var0
reduction: average
kind: r4
- file_name: test_static
time_units: hours
unlimdim: time
freq: -1 hours
varlist:
- module: ocn_mod
var_name: var2
reduction: none
kind: r4
_EOF

# remove any existing files that would result in false passes during checks
rm -f *.nc
my_test_count=1
printf "&diag_manager_nml \n use_modern_diag=.true. \n/" | cat > input.nml
test_expect_success "Running diag_manager and checking that the date was prepended correctly (test $my_test_count)" '
mpirun -n 1 ../test_prepend_date
'

cat <<_EOF > diag_table.yaml
title: test_prepend_date
base_date: 1 1 1 0 0 0
diag_files:
- file_name: test_non_static
time_units: hours
unlimdim: time
freq: 1 hours
varlist:
- module: ocn_mod
var_name: var0
reduction: average
kind: r4
- module: ocn_mod
var_name: var1
reduction: average
kind: r4
_EOF

printf "&diag_manager_nml \n use_modern_diag=.true. \n/ \n &test_prepend_date_nml \n pass_diag_time=.false. \n /" | cat > input.nml

test_expect_failure "Running diag_manager with fields that have a different start time (test $my_test_count)" '
mpirun -n 1 ../test_prepend_date
'

fi
test_done

0 comments on commit b554b32

Please sign in to comment.