Skip to content

Commit

Permalink
feat: updates for setting/getting base time variables and add test (N…
Browse files Browse the repository at this point in the history
  • Loading branch information
uramirez8707 authored and rem1776 committed May 1, 2024
1 parent 3a05694 commit aff30d6
Show file tree
Hide file tree
Showing 6 changed files with 169 additions and 81 deletions.
116 changes: 111 additions & 5 deletions diag_manager/diag_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,11 +48,13 @@
MODULE diag_data_mod
use platform_mod

USE time_manager_mod, ONLY: time_type
USE time_manager_mod, ONLY: get_calendar_type, NO_CALENDAR, set_date, set_time, month_name, time_type
USE constants_mod, ONLY: SECONDS_PER_HOUR, SECONDS_PER_MINUTE
USE mpp_domains_mod, ONLY: domain1d, domain2d, domainUG
USE fms_mod, ONLY: WARNING, write_version_number
USE fms_diag_bbox_mod, ONLY: fmsDiagIbounds_type

USE fms_mod, ONLY: write_version_number
use mpp_mod, ONLY: mpp_error, FATAL, WARNING, mpp_pe, mpp_root_pe, stdlog
#ifdef use_netCDF
! NF90_FILL_REAL has value of 9.9692099683868690e+36.
USE netcdf, ONLY: NF_FILL_REAL => NF90_FILL_REAL
use fms2_io_mod
Expand Down Expand Up @@ -370,8 +372,10 @@ MODULE diag_data_mod
! <!-- Global data for all files -->
TYPE(time_type) :: diag_init_time !< Time diag_manager_init called. If init_time not included in
!! diag_manager_init call, then same as base_time
TYPE(time_type) :: base_time
INTEGER :: base_year, base_month, base_day, base_hour, base_minute, base_second
TYPE(time_type), private :: base_time !< The base_time read from diag_table
logical, private :: base_time_set !< Flag indicating that the base_time is set
!! This is to prevent users from calling set_base_time multiple times
INTEGER, private :: base_year, base_month, base_day, base_hour, base_minute, base_second
CHARACTER(len = 256):: global_descriptor

! <!-- ALLOCATABLE variables -->
Expand Down Expand Up @@ -405,10 +409,112 @@ SUBROUTINE diag_data_init()

! Write version number out to log file
call write_version_number("DIAG_DATA_MOD", version)
module_is_initialized = .true.
base_time_set = .false.

END SUBROUTINE diag_data_init

!> @brief Set the module variable base_time
subroutine set_base_time(base_time_int)
integer :: base_time_int(6) !< base_time as an array [year month day hour min sec]

CHARACTER(len=9) :: amonth !< Month name
INTEGER :: stdlog_unit !< Fortran file unit number for the stdlog file.

if (.not. module_is_initialized) call mpp_error(FATAL, "set_base_time: diag_data is not initialized")
if (base_time_set) call mpp_error(FATAL, "set_base_time: the base_time is already set!")

base_year = base_time_int(1)
base_month = base_time_int(2)
base_day = base_time_int(3)
base_hour = base_time_int(4)
base_minute = base_time_int(5)
base_second = base_time_int(6)

! Set up the time type for base time
IF ( get_calendar_type() /= NO_CALENDAR ) THEN
IF ( base_year==0 .OR. base_month==0 .OR. base_day==0 ) THEN
call mpp_error(FATAL, 'diag_data_mod::set_base_time'//&
& 'The base_year/month/day can not equal zero')
END IF
base_time = set_date(base_year, base_month, base_day, base_hour, base_minute, base_second)
amonth = month_name(base_month)
ELSE
! No calendar - ignore year and month
base_time = set_time(NINT(base_hour*SECONDS_PER_HOUR)+NINT(base_minute*SECONDS_PER_MINUTE)+base_second, &
& base_day)
base_year = 0
base_month = 0
amonth = 'day'
END IF

! get the stdlog unit number
stdlog_unit = stdlog()

IF ( mpp_pe() == mpp_root_pe() ) THEN
WRITE (stdlog_unit,'("base date used = ",I4,1X,A,2I3,2(":",I2.2)," gmt")') base_year, TRIM(amonth), base_day, &
& base_hour, base_minute, base_second
END IF

base_time_set = .true.

end subroutine set_base_time

!> @brief gets the module variable base_time
!> @return the base_time
function get_base_time() &
result(res)
TYPE(time_type) :: res
res = base_time
end function get_base_time

!> @brief gets the module variable base_year
!> @return the base_year
function get_base_year() &
result(res)
integer :: res
res = base_year
end function get_base_year

!> @brief gets the module variable base_month
!> @return the base_month
function get_base_month() &
result(res)
integer :: res
res = base_month
end function get_base_month

!> @brief gets the module variable base_day
!> @return the base_day
function get_base_day() &
result(res)
integer :: res
res = base_day
end function get_base_day

!> @brief gets the module variable base_hour
!> @return the base_hour
function get_base_hour() &
result(res)
integer :: res
res = base_hour
end function get_base_hour

!> @brief gets the module variable base_minute
!> @return the base_minute
function get_base_minute() &
result(res)
integer :: res
res = base_minute
end function get_base_minute

!> @brief gets the module variable base_second
!> @return the base_second
function get_base_second() &
result(res)
integer :: res
res = base_second
end function get_base_second
END MODULE diag_data_mod
!> @}
! close documentation grouping
40 changes: 14 additions & 26 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -223,8 +223,8 @@ MODULE diag_manager_mod
USE diag_data_mod, ONLY: max_files, CMOR_MISSING_VALUE, DIAG_OTHER, DIAG_OCEAN, DIAG_ALL, EVERY_TIME,&
& END_OF_RUN, DIAG_SECONDS, DIAG_MINUTES, DIAG_HOURS, DIAG_DAYS, DIAG_MONTHS, DIAG_YEARS, num_files,&
& max_input_fields, max_output_fields, num_output_fields, EMPTY, FILL_VALUE, null_axis_id,&
& MAX_VALUE, MIN_VALUE, base_time, base_year, base_month, base_day,&
& base_hour, base_minute, base_second, global_descriptor, coord_type, files, input_fields,&
& MAX_VALUE, MIN_VALUE, get_base_time, get_base_year, get_base_month, get_base_day,&
& get_base_hour, get_base_minute, get_base_second, global_descriptor, coord_type, files, input_fields,&
& output_fields, Time_zero, append_pelist_name, mix_snapshot_average_fields,&
& first_send_data_call, do_diag_field_log, write_bytes_in_file, debug_diag_manager,&
& diag_log_unit, time_unit_list, pelist_name, max_axes, module_is_initialized, max_num_axis_sets,&
Expand Down Expand Up @@ -3941,7 +3941,7 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
diag_init_time = set_date(time_init(1), time_init(2), time_init(3), time_init(4),&
& time_init(5), time_init(6))
ELSE
diag_init_time = base_time
diag_init_time = get_base_time()
IF ( prepend_date .EQV. .TRUE. ) THEN
CALL error_mesg('diag_manager_mod::diag_manager_init',&
& 'prepend_date only supported when diag_manager_init is called with time_init present.', NOTE)
Expand All @@ -3952,13 +3952,13 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
#ifdef use_yaml
if (use_modern_diag) CALL diag_yaml_object_init(diag_subset_output)
#endif

CALL parse_diag_table(DIAG_SUBSET=diag_subset_output, ISTAT=mystat, ERR_MSG=err_msg_local)
IF ( mystat /= 0 ) THEN
if (.not. use_modern_diag) then
CALL parse_diag_table(DIAG_SUBSET=diag_subset_output, ISTAT=mystat, ERR_MSG=err_msg_local)
IF ( mystat /= 0 ) THEN
IF ( fms_error_handler('diag_manager_mod::diag_manager_init',&
& 'Error parsing diag_table. '//TRIM(err_msg_local), err_msg) ) RETURN
END IF

END IF
endif
!initialize files%bytes_written to zero
files(:)%bytes_written = 0

Expand All @@ -3983,18 +3983,6 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
RETURN
END SUBROUTINE diag_manager_init

!> @brief Return base time for diagnostics.
!! @return time_type get_base_time
!! @details Return base time for diagnostics (note: base time must be >= model time).
TYPE(time_type) FUNCTION get_base_time ()
! <ERROR STATUS="FATAL">
! MODULE has not been initialized
! </ERROR>
IF ( .NOT.module_is_initialized ) CALL error_mesg('diag_manager_mod::get_base_time', &
& 'module has not been initialized', FATAL)
get_base_time = base_time
END FUNCTION get_base_time

!> @brief Return base date for diagnostics.
!! @details Return date information for diagnostic reference time.
SUBROUTINE get_base_date(year, month, day, hour, minute, second)
Expand All @@ -4003,12 +3991,12 @@ SUBROUTINE get_base_date(year, month, day, hour, minute, second)
! <ERROR STATUS="FATAL">module has not been initialized</ERROR>
IF (.NOT.module_is_initialized) CALL error_mesg ('diag_manager_mod::get_base_date', &
& 'module has not been initialized', FATAL)
year = base_year
month = base_month
day = base_day
hour = base_hour
minute = base_minute
second = base_second
year = get_base_year()
month = get_base_month()
day = get_base_day()
hour = get_base_hour()
minute = get_base_minute()
second = get_base_second()
END SUBROUTINE get_base_date

!> @brief Determine whether data is needed for the current model time step.
Expand Down
44 changes: 8 additions & 36 deletions diag_manager/diag_table.F90
Original file line number Diff line number Diff line change
Expand Up @@ -250,12 +250,10 @@
MODULE diag_table_mod

USE fms2_io_mod, ONLY: ascii_read
USE fms_mod, ONLY: fms_error_handler, error_mesg, stdlog, mpp_pe, mpp_root_pe, FATAL, WARNING, lowercase
USE time_manager_mod, ONLY: get_calendar_type, NO_CALENDAR, set_date, set_time, month_name, time_type
USE constants_mod, ONLY: SECONDS_PER_HOUR, SECONDS_PER_MINUTE

USE diag_data_mod, ONLY: global_descriptor, base_time, base_year, base_month, base_day, base_hour, base_minute, &
& base_second, DIAG_OTHER, DIAG_OCEAN, DIAG_ALL, coord_type, append_pelist_name, pelist_name
USE fms_mod, ONLY: fms_error_handler, error_mesg, mpp_pe, mpp_root_pe, FATAL, WARNING, lowercase
USE time_manager_mod, ONLY: set_date, time_type
USE diag_data_mod, ONLY: global_descriptor, get_base_time, set_base_time, &
& DIAG_OTHER, DIAG_OCEAN, DIAG_ALL, coord_type, append_pelist_name, pelist_name
USE diag_util_mod, ONLY: init_file, check_duplicate_output_fields, init_input_field, init_output_field

IMPLICIT NONE
Expand Down Expand Up @@ -325,7 +323,6 @@ SUBROUTINE parse_diag_table(diag_subset, istat, err_msg)

INTEGER, PARAMETER :: DT_LINE_LENGTH = 256

INTEGER :: stdlog_unit !< Fortran file unit number for the stdlog file.
INTEGER :: record_len !< String length of the diag_table line read in.
INTEGER :: num_lines !< Number of lines in diag_table
INTEGER :: line_num !< Integer representation of the line number.
Expand All @@ -337,10 +334,10 @@ SUBROUTINE parse_diag_table(diag_subset, istat, err_msg)
INTEGER, POINTER :: pstat !< pointer that points to istat if preset, otherwise, points to mystat.

CHARACTER(len=5) :: line_number !< String representation of the line number.
CHARACTER(len=9) :: amonth !< Month name
CHARACTER(len=256) :: record_line !< Current line from the diag_table.
CHARACTER(len=256) :: local_err_msg !< Sting to hold local error messages.
CHARACTER(len=:), DIMENSION(:), ALLOCATABLE :: diag_table
integer :: base_time_int(6) !< The base time as read in from the table [year month day hour min sec]

TYPE(file_description_type) :: temp_file
TYPE(field_description_type) :: temp_field
Expand All @@ -360,9 +357,6 @@ SUBROUTINE parse_diag_table(diag_subset, istat, err_msg)
diag_subset_output = DIAG_ALL
END IF

! get the stdlog unit number
stdlog_unit = stdlog()

call ascii_read('diag_table', diag_table, num_lines=num_lines)

! Read in the global file labeling string
Expand All @@ -374,36 +368,14 @@ SUBROUTINE parse_diag_table(diag_subset, istat, err_msg)
END IF

! Read in the base date
READ (UNIT=diag_table(2), FMT=*, IOSTAT=mystat) base_year, base_month, base_day, base_hour, base_minute, &
& base_second
READ (UNIT=diag_table(2), FMT=*, IOSTAT=mystat) base_time_int
IF ( mystat /= 0 ) THEN
pstat = mystat
IF ( fms_error_handler('diag_manager_init', 'Error reading the base date from the diagnostic table.', &
& err_msg) ) RETURN
END IF

! Set up the time type for base time
IF ( get_calendar_type() /= NO_CALENDAR ) THEN
IF ( base_year==0 .OR. base_month==0 .OR. base_day==0 ) THEN
pstat = 101
IF ( fms_error_handler('diag_table_mod::parse_diag_table', &
& 'The base_year/month/day can not equal zero', err_msg) ) RETURN
END IF
base_time = set_date(base_year, base_month, base_day, base_hour, base_minute, base_second)
amonth = month_name(base_month)
ELSE
! No calendar - ignore year and month
base_time = set_time(NINT(base_hour*SECONDS_PER_HOUR)+NINT(base_minute*SECONDS_PER_MINUTE)+base_second, &
& base_day)
base_year = 0
base_month = 0
amonth = 'day'
END IF

IF ( mpp_pe() == mpp_root_pe() ) THEN
WRITE (stdlog_unit,'("base date used = ",I4,1X,A,2I3,2(":",I2.2)," gmt")') base_year, TRIM(amonth), base_day, &
& base_hour, base_minute, base_second
END IF
call set_base_time(base_time_int)

nfiles=0
nfields=0
Expand Down Expand Up @@ -656,7 +628,7 @@ TYPE(file_description_type) FUNCTION parse_file_line(line, istat, err_msg)
parse_file_line%iFile_duration_units = parse_file_line%iNew_file_freq_units
END IF
ELSE
parse_file_line%start_time = base_time
parse_file_line%start_time = get_base_time()
parse_file_line%file_duration = parse_file_line%new_file_freq
parse_file_line%iFile_duration_units = parse_file_line%iNew_file_freq_units
END IF
Expand Down
24 changes: 12 additions & 12 deletions diag_manager/diag_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -42,9 +42,9 @@ MODULE diag_util_mod

USE diag_data_mod, ONLY: output_fields, input_fields, files, do_diag_field_log, diag_log_unit,&
& VERY_LARGE_AXIS_LENGTH, time_zero, VERY_LARGE_FILE_FREQ, END_OF_RUN, EVERY_TIME,&
& DIAG_SECONDS, DIAG_MINUTES, DIAG_HOURS, DIAG_DAYS, DIAG_MONTHS, DIAG_YEARS, base_time,&
& time_unit_list, max_files, base_year, base_month, base_day, base_hour, base_minute,&
& base_second, num_files, max_files, max_fields_per_file, max_out_per_in_field,&
& DIAG_SECONDS, DIAG_MINUTES, DIAG_HOURS, DIAG_DAYS, DIAG_MONTHS, DIAG_YEARS, get_base_time,&
& time_unit_list, max_files, get_base_year, get_base_month, get_base_day, get_base_hour, get_base_minute,&
& get_base_second, num_files, max_files, max_fields_per_file, max_out_per_in_field,&
& max_input_fields,num_input_fields, max_output_fields, num_output_fields, coord_type,&
& mix_snapshot_average_fields, global_descriptor, CMOR_MISSING_VALUE, use_cmor, pack_size,&
& debug_diag_manager, flush_nc_files, output_field_type, max_field_attributes, max_file_attributes,&
Expand Down Expand Up @@ -1194,7 +1194,7 @@ SUBROUTINE init_file(name, output_freq, output_units, format, time_units, long_n
files(num_files)%long_name = TRIM(long_name)
files(num_files)%num_fields = 0
files(num_files)%local = .FALSE.
files(num_files)%last_flush = base_time
files(num_files)%last_flush = get_base_time()
files(num_files)%file_unit = -1
files(num_files)%new_file_freq = new_file_freq1
files(num_files)%new_file_freq_units = new_file_freq_units1
Expand All @@ -1208,7 +1208,7 @@ SUBROUTINE init_file(name, output_freq, output_units, format, time_units, long_n
IF ( PRESENT(start_time) ) THEN
files(num_files)%start_time = start_time
ELSE
files(num_files)%start_time = base_time
files(num_files)%start_time = get_base_time()
END IF
files(num_files)%next_open=diag_time_inc(files(num_files)%start_time,new_file_freq1,new_file_freq_units1)
files(num_files)%close_time = diag_time_inc(files(num_files)%start_time,file_duration1, file_duration_units1)
Expand All @@ -1222,8 +1222,8 @@ SUBROUTINE init_file(name, output_freq, output_units, format, time_units, long_n
END IF

! add time_axis_id and time_bounds_id here
WRITE(time_units_str, 11) TRIM(time_unit_list(files(num_files)%time_units)), base_year,&
& base_month, base_day, base_hour, base_minute, base_second
WRITE(time_units_str, 11) TRIM(time_unit_list(files(num_files)%time_units)), get_base_year(),&
& get_base_month(), get_base_day(), get_base_hour(), get_base_minute(), get_base_second()
11 FORMAT(a, ' since ', i4.4, '-', i2.2, '-', i2.2, ' ', i2.2, ':', i2.2, ':', i2.2)
files(num_files)%time_axis_id = diag_axis_init (TRIM(long_name), tdata, time_units_str, 'T',&
& TRIM(long_name) , set_name=TRIM(name) )
Expand Down Expand Up @@ -1738,8 +1738,8 @@ SUBROUTINE opening_file(file, time, filename_time)
match_req_fields = .FALSE.

! Here is where time_units string must be set up; time since base date
WRITE (time_units, 11) TRIM(time_unit_list(files(file)%time_units)), base_year,&
& base_month, base_day, base_hour, base_minute, base_second
WRITE (time_units, 11) TRIM(time_unit_list(files(file)%time_units)), get_base_year(),&
& get_base_month(), get_base_day(), get_base_hour(), get_base_minute(), get_base_second()
11 FORMAT(A, ' since ', I4.4, '-', I2.2, '-', I2.2, ' ', I2.2, ':', I2.2, ':', I2.2)
base_name = files(file)%name
IF ( files(file)%new_file_freq < VERY_LARGE_FILE_FREQ ) THEN
Expand Down Expand Up @@ -2332,7 +2332,7 @@ SUBROUTINE diag_data_out(file, field, dat, time, final_call_in, static_write_in,
static_write = .FALSE.
IF ( PRESENT(static_write_in) ) static_write = static_write_in
!> dif is the time as a real that is evaluated
dif = get_date_dif(time, base_time, files(file)%time_units)
dif = get_date_dif(time, get_base_time(), files(file)%time_units)

! get file_unit, open new file and close curent file if necessary
IF ( .NOT.static_write .OR. files(file)%file_unit < 0 ) &
Expand Down Expand Up @@ -2367,9 +2367,9 @@ SUBROUTINE diag_data_out(file, field, dat, time, final_call_in, static_write_in,
IF ( .NOT.output_fields(field)%written_once ) output_fields(field)%written_once = .TRUE.
! *** inserted this line because start_dif < 0 for static fields ***
IF ( .NOT.output_fields(field)%static ) THEN
start_dif = get_date_dif(output_fields(field)%last_output, base_time,files(file)%time_units)
start_dif = get_date_dif(output_fields(field)%last_output, get_base_time(),files(file)%time_units)
IF ( .NOT.mix_snapshot_average_fields ) THEN
end_dif = get_date_dif(output_fields(field)%next_output, base_time, files(file)%time_units)
end_dif = get_date_dif(output_fields(field)%next_output, get_base_time(), files(file)%time_units)
ELSE
end_dif = dif
END IF
Expand Down
Loading

0 comments on commit aff30d6

Please sign in to comment.