Skip to content

Commit

Permalink
Crash if using mix_snapshot_average_fields = .true. with the new diag…
Browse files Browse the repository at this point in the history
… manager, crash if mixing averaged and non averaged fields in the same file, add tests to confirm
  • Loading branch information
uramirez8707 committed May 2, 2024
1 parent 720d7c7 commit 4c290de
Show file tree
Hide file tree
Showing 3 changed files with 63 additions and 4 deletions.
8 changes: 6 additions & 2 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4173,11 +4173,15 @@ SUBROUTINE diag_manager_init(diag_model_subset, time_init, err_msg)
END IF

IF ( mix_snapshot_average_fields ) THEN
IF ( mpp_pe() == mpp_root_pe() ) THEN
IF ( .not. use_modern_diag ) THEN
CALL error_mesg('diag_manager_mod::diag_manager_init', 'Setting diag_manager_nml variable '//&
& 'mix_snapshot_average_fields = .TRUE. will cause ERRORS in the time coordinates '//&
& 'of all time averaged fields. Strongly recommend setting mix_snapshot_average_fields '//&
& '= .FALSE.', WARNING)
& '= .FALSE.', NOTE)
ELSE
CALL error_mesg('diag_manager_mod::diag_manager_init', 'mix_snapshot_average_fields = .TRUE. is not '//&
& 'supported if use_modern_diag = .TRUE. Please set mix_snapshot_average_fields '//&
& 'to .FALSE. and put instantaneous and averaged fields in seperate files!', FATAL)
END IF
END IF
ALLOCATE(output_fields(max_output_fields))
Expand Down
26 changes: 24 additions & 2 deletions diag_manager/fms_diag_yaml.F90
Original file line number Diff line number Diff line change
Expand Up @@ -371,6 +371,7 @@ subroutine diag_yaml_object_init(diag_subset_output)
logical :: allow_averages !< .True. if averages are allowed (the file is not static of you are
!! outputing data at every frequency)
character(len=:), allocatable :: filename!< Diag file name (for error messages)
logical :: is_instantaneous !< .True. if the file is instantaneous (i.e no averaging)

if (diag_yaml_module_initialized) return

Expand Down Expand Up @@ -450,6 +451,7 @@ subroutine diag_yaml_object_init(diag_subset_output)
allocate(diag_yaml%diag_files(file_count)%file_varlist(get_total_num_vars(diag_yaml_id, diag_file_ids(i))))
allocate(diag_yaml%diag_files(file_count)%file_outlist(get_total_num_vars(diag_yaml_id, diag_file_ids(i))))
allow_averages = .not. diag_yaml%diag_files(file_count)%file_freq(1) < 1
is_instantaneous = .false.
nvars_loop: do j = 1, nvars
write_var = .true.
call get_value_from_key(diag_yaml_id, var_ids(j), "write_var", write_var, is_optional=.true.)
Expand All @@ -465,7 +467,8 @@ subroutine diag_yaml_object_init(diag_subset_output)
diag_yaml%diag_fields(var_count)%var_axes_names = ""
diag_yaml%diag_fields(var_count)%var_file_is_subregional = diag_yaml%diag_files(file_count)%has_file_sub_region()

call fill_in_diag_fields(diag_yaml_id, var_ids(j), diag_yaml%diag_fields(var_count), allow_averages)
call fill_in_diag_fields(diag_yaml_id, var_ids(j), diag_yaml%diag_fields(var_count), allow_averages, &
j .eq. 1, is_instantaneous)

!> Save the variable name in the diag_file type
diag_yaml%diag_files(file_count)%file_varlist(file_var_count) = diag_yaml%diag_fields(var_count)%var_varname
Expand Down Expand Up @@ -605,11 +608,16 @@ subroutine fill_in_diag_files(diag_yaml_id, diag_file_id, yaml_fileobj)

!> @brief Fills in a diagYamlFilesVar_type with the contents of a variable block in
!! diag_table.yaml
subroutine fill_in_diag_fields(diag_file_id, var_id, field, allow_averages)
subroutine fill_in_diag_fields(diag_file_id, var_id, field, allow_averages, first_variable_in_file, &
is_instantaneous)
integer, intent(in) :: diag_file_id !< Id of the file block in the yaml file
integer, intent(in) :: var_id !< Id of the variable block in the yaml file
type(diagYamlFilesVar_type), intent(inout) :: field !< diagYamlFilesVar_type obj to read the contents into
logical, intent(in) :: allow_averages !< .True. if averages are allowed for this file
logical, intent(in) :: first_variable_in_file !< .True. if this is the first variable
!! in the file
logical, intent(inout) :: is_instantaneous !< .True. if the file is instantaneous, so averaged
!! fields are not allowed

integer :: natt !< Number of attributes in variable
integer :: var_att_id(1) !< Id of the variable attribute block
Expand All @@ -630,6 +638,20 @@ subroutine fill_in_diag_fields(diag_file_id, var_id, field, allow_averages)
"Check your diag_table.yaml for the field:"//trim(field%var_varname))
endif

!! This is to prevent mixing instantaneous and averaged fields in the same file
if (first_variable_in_file) then
if (field%var_reduction .eq. time_none) then
is_instantaneous = .true.
else
is_instantaneous = .false.
endif
else
if ((is_instantaneous .and. field%var_reduction .ne. time_none) &
.or. (.not. is_instantaneous .and. field%var_reduction .eq. time_none)) &
call mpp_error(FATAL, "The file "//field%var_fname//" is mixing instantaneous and non-instantaneous "//&
"fields which is not allowed as it will cause the times in your file to be wrong.")
endif

call diag_get_value_from_key(diag_file_id, var_id, "module", field%var_module)
deallocate(buffer)
call diag_get_value_from_key(diag_file_id, var_id, "kind", buffer)
Expand Down
33 changes: 33 additions & 0 deletions test_fms/diag_manager/test_time_avg.sh
Original file line number Diff line number Diff line change
Expand Up @@ -192,6 +192,39 @@ test_expect_success "Checking answers for the "avg" reduction method with halo o
mpirun -n 1 ../check_time_avg
'

my_test_count=`expr $my_test_count + 1`
printf "&diag_manager_nml \n use_modern_diag=.true. \n mix_snapshot_average_fields = .true. \n /" | cat > input.nml
test_expect_failure "Running diag_manager with with mix_snapshot_average_fields = .true. (test $my_test_count)" '
mpirun -n 6 ../test_reduction_methods
'

cat <<_EOF > diag_table.yaml
title: test_avg
base_date: 2 1 1 0 0 0
diag_files:
- file_name: test_avg
time_units: hours
unlimdim: time
freq: 6 hours
varlist:
- module: ocn_mod
var_name: var0
output_name: var0_avg
reduction: average
kind: r4
- module: ocn_mod
var_name: var0
output_name: var0_none
reduction: none
kind: r4
_EOF

my_test_count=`expr $my_test_count + 1`
printf "&diag_manager_nml \n use_modern_diag=.true. \n /" | cat > input.nml
test_expect_failure "Running diag_manager with with a file with instantaneous and averaged output (test $my_test_count)" '
mpirun -n 6 ../test_reduction_methods
'

cat <<_EOF > diag_table.yaml
title: test_avg
base_date: 2 1 1 0 0 0
Expand Down

0 comments on commit 4c290de

Please sign in to comment.