Skip to content

Commit

Permalink
+Use answer_date to specify remapping
Browse files Browse the repository at this point in the history
  Replace answers_2018 arguments with answer_date arguments to specify the
version of expressions used in a number of vertical or horizontal regridding
calls.  In some cases, this also involves replacing one of the elements in an
opaque type.  It can also involve reading (but not yet logging) the new runtime
parameter DEFAULT_ANSWER_DATE, but if it not set the results are unchanged from
before.  There is also a new optional argument, remap_answer_date, to
wave_speed_init and wave_speed_set_param.  Some comments were also added to
describe real variables in VarMix_init.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Jul 29, 2022
1 parent ecb85cb commit 7c72377
Show file tree
Hide file tree
Showing 13 changed files with 293 additions and 103 deletions.
29 changes: 21 additions & 8 deletions src/core/MOM_open_boundary.F90
Original file line number Diff line number Diff line change
Expand Up @@ -321,9 +321,10 @@ module MOM_open_boundary
real :: ramp_value !< If ramp is True, where we are on the ramp from
!! zero to one [nondim].
type(time_type) :: ramp_start_time !< Time when model was started.
logical :: answers_2018 !< If true, use the order of arithmetic and expressions for remapping
!! that recover the answers from the end of 2018. Otherwise, use more
!! robust and accurate forms of mathematically equivalent expressions.
integer :: remap_answer_date !< The vintage of the order of arithmetic and expressions to use
!! for remapping. Values below 20190101 recover the remapping
!! answers from 2018, while higher values use more robust
!! forms of the same remapping expressions.
end type ocean_OBC_type

!> Control structure for open boundaries that read from files.
Expand Down Expand Up @@ -371,7 +372,11 @@ subroutine open_boundary_config(G, US, param_file, OBC)
character(len=1024) :: segment_str ! The contents (rhs) for parameter "segment_param_str"
character(len=200) :: config1 ! String for OBC_USER_CONFIG
real :: Lscale_in, Lscale_out ! parameters controlling tracer values at the boundaries [L ~> m]
logical :: answers_2018, default_2018_answers
logical :: answers_2018 ! If true, use the order of arithmetic and expressions for remapping
! that recover the answers from the end of 2018. Otherwise, use more
! robust and accurate forms of mathematically equivalent expressions.
integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags.
logical :: default_2018_answers ! The default setting for the various 2018_ANSWERS flags.
logical :: check_reconstruction, check_remapping, force_bounds_in_subcell
character(len=64) :: remappingScheme
! This include declares and sets the variable "version".
Expand Down Expand Up @@ -618,18 +623,26 @@ subroutine open_boundary_config(G, US, param_file, OBC)
"If true, the values on the intermediate grid used for remapping "//&
"are forced to be bounded, which might not be the case due to "//&
"round off.", default=.false.,do_not_log=.true.)
call get_param(param_file, mdl, "DEFAULT_ANSWER_DATE", default_answer_date, &
"This sets the default value for the various _ANSWER_DATE parameters.", &
default=99991231, do_not_log=.true.)
call get_param(param_file, mdl, "DEFAULT_2018_ANSWERS", default_2018_answers, &
"This sets the default value for the various _2018_ANSWERS parameters.", &
default=.false.)
call get_param(param_file, mdl, "REMAPPING_2018_ANSWERS", OBC%answers_2018, &
default=(default_answer_date<20190101))
call get_param(param_file, mdl, "REMAPPING_2018_ANSWERS", answers_2018, &
"If true, use the order of arithmetic and expressions that recover the "//&
"answers from the end of 2018. Otherwise, use updated and more robust "//&
"forms of the same expressions.", default=default_2018_answers)
if (answers_2018) then
OBC%remap_answer_date = 20181231
else
OBC%remap_answer_date = 20190101
endif

allocate(OBC%remap_CS)
call initialize_remapping(OBC%remap_CS, remappingScheme, boundary_extrapolation = .false., &
check_reconstruction=check_reconstruction, check_remapping=check_remapping, &
force_bounds_in_subcell=force_bounds_in_subcell, answers_2018=OBC%answers_2018)
force_bounds_in_subcell=force_bounds_in_subcell, answer_date=OBC%remap_answer_date)

endif ! OBC%number_of_segments > 0

Expand Down Expand Up @@ -3718,7 +3731,7 @@ subroutine update_OBC_segment_data(G, GV, US, OBC, tv, h, Time)

if (OBC%add_tide_constituents) time_delta = US%s_to_T * time_type_to_real(Time - OBC%time_ref)

if (.not. OBC%answers_2018) then
if (OBC%remap_answer_date >= 20190101) then
h_neglect = GV%H_subroundoff ; h_neglect_edge = GV%H_subroundoff
elseif (GV%Boussinesq) then
h_neglect = GV%m_to_H * 1.0e-30 ; h_neglect_edge = GV%m_to_H * 1.0e-10
Expand Down
21 changes: 18 additions & 3 deletions src/diagnostics/MOM_diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1551,7 +1551,13 @@ subroutine MOM_diagnostics_init(MIS, ADp, CDp, Time, G, GV, US, param_file, diag
character(len=40) :: mdl = "MOM_diagnostics" ! This module's name.
character(len=48) :: thickness_units, flux_units
logical :: use_temperature, adiabatic
logical :: default_2018_answers, remap_answers_2018
integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags.
logical :: default_2018_answers ! The default setting for the various 2018_ANSWERS flags.
integer :: remap_answer_date ! The vintage of the order of arithmetic and expressions to use
! for remapping. Values below 20190101 recover the remapping
! answers from 2018, while higher values use more robust
! forms of the same remapping expressions.
logical :: remap_answers_2018

CS%initialized = .true.

Expand Down Expand Up @@ -1579,13 +1585,22 @@ subroutine MOM_diagnostics_init(MIS, ADp, CDp, Time, G, GV, US, param_file, diag
call get_param(param_file, mdl, "INTERNAL_WAVE_SPEED_BETTER_EST", better_speed_est, &
"If true, use a more robust estimate of the first mode wave speed as the "//&
"starting point for iterations.", default=.true.)
call get_param(param_file, mdl, "DEFAULT_ANSWER_DATE", default_answer_date, &
"This sets the default value for the various _ANSWER_DATE parameters.", &
default=99991231, do_not_log=.true.)
call get_param(param_file, mdl, "DEFAULT_2018_ANSWERS", default_2018_answers, &
"This sets the default value for the various _2018_ANSWERS parameters.", &
default=.false.)
default=(default_answer_date<20190101))
call get_param(param_file, mdl, "REMAPPING_2018_ANSWERS", remap_answers_2018, &
"If true, use the order of arithmetic and expressions that recover the "//&
"answers from the end of 2018. Otherwise, use updated and more robust "//&
"forms of the same expressions.", default=default_2018_answers)
if (remap_answers_2018) then
remap_answer_date = 20181231
else
remap_answer_date = 20190101
endif

call get_param(param_file, mdl, "SPLIT", split, default=.true., do_not_log=.true.)

if (GV%Boussinesq) then
Expand Down Expand Up @@ -1813,7 +1828,7 @@ subroutine MOM_diagnostics_init(MIS, ADp, CDp, Time, G, GV, US, param_file, diag
if ((CS%id_cg1>0) .or. (CS%id_Rd1>0) .or. (CS%id_cfl_cg1>0) .or. &
(CS%id_cfl_cg1_x>0) .or. (CS%id_cfl_cg1_y>0) .or. &
(CS%id_cg_ebt>0) .or. (CS%id_Rd_ebt>0) .or. (CS%id_p_ebt>0)) then
call wave_speed_init(CS%wave_speed, remap_answers_2018=remap_answers_2018, &
call wave_speed_init(CS%wave_speed, remap_answer_date=remap_answer_date, &
better_speed_est=better_speed_est, min_speed=wave_speed_min, &
wave_speed_tol=wave_speed_tol)
endif
Expand Down
35 changes: 27 additions & 8 deletions src/diagnostics/MOM_wave_speed.F90
Original file line number Diff line number Diff line change
Expand Up @@ -46,9 +46,11 @@ module MOM_wave_speed
!! speeds [nondim]
type(remapping_CS) :: remapping_CS !< Used for vertical remapping when calculating equivalent barotropic
!! mode structure.
logical :: remap_answers_2018 = .true. !< If true, use the order of arithmetic and expressions that
!! recover the remapping answers from 2018. If false, use more
!! robust forms of the same remapping expressions.
integer :: remap_answer_date = 20181231 !< The vintage of the order of arithmetic and expressions to use
!! for remapping. Values below 20190101 recover the remapping
!! answers from 2018, while higher values use more robust
!! forms of the same remapping expressions.
!### Change to 99991231?
type(diag_ctrl), pointer :: diag !< Diagnostics control structure
end type wave_speed_CS

Expand Down Expand Up @@ -558,7 +560,7 @@ subroutine wave_speed(h, tv, G, GV, US, cg1, CS, full_halos, use_ebt_mode, mono_
do k = 1,kc
Hc_H(k) = GV%Z_to_H * Hc(k)
enddo
if (CS%remap_answers_2018) then
if (CS%remap_answer_date < 20190101) then
call remapping_core_h(CS%remapping_CS, kc, Hc_H(:), mode_struct, &
nz, h(i,j,:), modal_structure(i,j,:), &
1.0e-30*GV%m_to_H, 1.0e-10*GV%m_to_H)
Expand Down Expand Up @@ -1168,7 +1170,7 @@ end subroutine tridiag_det

!> Initialize control structure for MOM_wave_speed
subroutine wave_speed_init(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_depth, remap_answers_2018, &
better_speed_est, min_speed, wave_speed_tol)
remap_answer_date, better_speed_est, min_speed, wave_speed_tol)
type(wave_speed_CS), intent(inout) :: CS !< Wave speed control struct
logical, optional, intent(in) :: use_ebt_mode !< If true, use the equivalent
!! barotropic mode instead of the first baroclinic mode.
Expand All @@ -1181,6 +1183,10 @@ subroutine wave_speed_init(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_de
logical, optional, intent(in) :: remap_answers_2018 !< If true, use the order of arithmetic and expressions
!! that recover the remapping answers from 2018. Otherwise
!! use more robust but mathematically equivalent expressions.
integer, optional, intent(in) :: remap_answer_date !< The vintage of the order of arithmetic and expressions
!! to use for remapping. Values below 20190101 recover the remapping
!! answers from 2018, while higher values use more robust
!! forms of the same remapping expressions.
logical, optional, intent(in) :: better_speed_est !< If true, use a more robust estimate of the first
!! mode speed as the starting point for iterations.
real, optional, intent(in) :: min_speed !< If present, set a floor in the first mode speed
Expand All @@ -1199,15 +1205,17 @@ subroutine wave_speed_init(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_de

call wave_speed_set_param(CS, use_ebt_mode=use_ebt_mode, mono_N2_column_fraction=mono_N2_column_fraction, &
better_speed_est=better_speed_est, min_speed=min_speed, wave_speed_tol=wave_speed_tol)
!### Uncomment this? remap_answers_2018=remap_answers_2018, remap_answer_date=remap_answer_date)

!### The remap_answers_2018 argument is irrelevant, because remapping is hard-coded to use PLM.
call initialize_remapping(CS%remapping_CS, 'PLM', boundary_extrapolation=.false., &
answers_2018=CS%remap_answers_2018)
answer_date=CS%remap_answer_date)

end subroutine wave_speed_init

!> Sets internal parameters for MOM_wave_speed
subroutine wave_speed_set_param(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_depth, remap_answers_2018, &
better_speed_est, min_speed, wave_speed_tol)
remap_answer_date, better_speed_est, min_speed, wave_speed_tol)
type(wave_speed_CS), intent(inout) :: CS
!< Control structure for MOM_wave_speed
logical, optional, intent(in) :: use_ebt_mode !< If true, use the equivalent
Expand All @@ -1221,6 +1229,10 @@ subroutine wave_speed_set_param(CS, use_ebt_mode, mono_N2_column_fraction, mono_
logical, optional, intent(in) :: remap_answers_2018 !< If true, use the order of arithmetic and expressions
!! that recover the remapping answers from 2018. Otherwise
!! use more robust but mathematically equivalent expressions.
integer, optional, intent(in) :: remap_answer_date !< The vintage of the order of arithmetic and expressions
!! to use for remapping. Values below 20190101 recover the remapping
!! answers from 2018, while higher values use more robust
!! forms of the same remapping expressions.
logical, optional, intent(in) :: better_speed_est !< If true, use a more robust estimate of the first
!! mode speed as the starting point for iterations.
real, optional, intent(in) :: min_speed !< If present, set a floor in the first mode speed
Expand All @@ -1231,7 +1243,14 @@ subroutine wave_speed_set_param(CS, use_ebt_mode, mono_N2_column_fraction, mono_
if (present(use_ebt_mode)) CS%use_ebt_mode = use_ebt_mode
if (present(mono_N2_column_fraction)) CS%mono_N2_column_fraction = mono_N2_column_fraction
if (present(mono_N2_depth)) CS%mono_N2_depth = mono_N2_depth
if (present(remap_answers_2018)) CS%remap_answers_2018 = remap_answers_2018
if (present(remap_answers_2018)) then
if (remap_answers_2018) then
CS%remap_answer_date = 20181231
else
CS%remap_answer_date = 20190101
endif
endif
if (present(remap_answer_date)) CS%remap_answer_date = remap_answer_date
if (present(better_speed_est)) CS%better_cg1_est = better_speed_est
if (present(min_speed)) CS%min_speed2 = min_speed**2
if (present(wave_speed_tol)) CS%wave_speed_tol = wave_speed_tol
Expand Down
24 changes: 20 additions & 4 deletions src/framework/MOM_diag_mediator.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3144,7 +3144,15 @@ subroutine diag_mediator_init(G, GV, US, nz, param_file, diag_cs, doc_file_dir)
! Local variables
integer :: ios, i, new_unit
logical :: opened, new_file
logical :: answers_2018, default_2018_answers
logical :: remap_answers_2018 ! If true, use the order of arithmetic and expressions that
! recover the remapping answers from 2018. If false, use more
! robust forms of the same remapping expressions.
integer :: remap_answer_date ! The vintage of the order of arithmetic and expressions to use
! for remapping. Values below 20190101 recover the remapping
! answers from 2018, while higher values use more robust
! forms of the same remapping expressions.
integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags.
logical :: default_2018_answers ! The default setting for the various 2018_ANSWERS flags.
character(len=8) :: this_pe
character(len=240) :: doc_file, doc_file_dflt, doc_path
character(len=240), allocatable :: diag_coords(:)
Expand All @@ -3171,13 +3179,21 @@ subroutine diag_mediator_init(G, GV, US, nz, param_file, diag_cs, doc_file_dir)
'The number of diagnostic vertical coordinates to use. '//&
'For each coordinate, an entry in DIAG_COORDS must be provided.', &
default=1)
call get_param(param_file, mdl, "DEFAULT_ANSWER_DATE", default_answer_date, &
"This sets the default value for the various _ANSWER_DATE parameters.", &
default=99991231, do_not_log=.true.)
call get_param(param_file, mdl, "DEFAULT_2018_ANSWERS", default_2018_answers, &
"This sets the default value for the various _2018_ANSWERS parameters.", &
default=.false.)
call get_param(param_file, mdl, "REMAPPING_2018_ANSWERS", answers_2018, &
default=(default_answer_date<20190101))
call get_param(param_file, mdl, "REMAPPING_2018_ANSWERS", remap_answers_2018, &
"If true, use the order of arithmetic and expressions that recover the "//&
"answers from the end of 2018. Otherwise, use updated and more robust "//&
"forms of the same expressions.", default=default_2018_answers)
if (remap_answers_2018) then
remap_answer_date = 20181231
else
remap_answer_date = 20190101
endif
call get_param(param_file, mdl, 'USE_GRID_SPACE_DIAGNOSTIC_AXES', diag_cs%grid_space_axes, &
'If true, use a grid index coordinate convention for diagnostic axes. ',&
default=.false.)
Expand All @@ -3200,7 +3216,7 @@ subroutine diag_mediator_init(G, GV, US, nz, param_file, diag_cs, doc_file_dir)
allocate(diag_cs%diag_remap_cs(diag_cs%num_diag_coords))
! Initialize each diagnostic vertical coordinate
do i=1, diag_cs%num_diag_coords
call diag_remap_init(diag_cs%diag_remap_cs(i), diag_coords(i), answers_2018=answers_2018)
call diag_remap_init(diag_cs%diag_remap_cs(i), diag_coords(i), answer_date=remap_answer_date)
enddo
deallocate(diag_coords)
endif
Expand Down
Loading

0 comments on commit 7c72377

Please sign in to comment.