Skip to content

Commit

Permalink
+FIX_USTAR_GUSTLESS_BUG is now USTAR_GUSTLESS_BUG
Browse files Browse the repository at this point in the history
  Renamed the runtime parameter FIX_USTAR_GUSTLESS_BUG to USTAR_GUSTLESS_BUG
(with a switch between the meanings of true and false for the two parameters)
for consistency with the syntax of other bug-fix flags in MOM6 and to partially
address dev/gfdl MOM6 issue mom-ocean#237.  Input parameter files need not be changed
right away because MOM6 will still work if FIX_USTAR_GUSTLESS_BUG is specified
instead of USTAR_GUSTLESS_BUG, but USTAR_GUSTLESS_BUG will be logged, so there
are changes to the MOM_parameter_doc files.   By default or with existing input
parameter files, all answers are bitwise identical, and there is error handling
if inconsistent settings of FIX_USTAR_GUSTLESS_BUG and USTAR_GUSTLESS_BUG are
both specified.
  • Loading branch information
Hallberg-NOAA committed Dec 15, 2023
1 parent 4e8fbe1 commit 7b97002
Show file tree
Hide file tree
Showing 4 changed files with 115 additions and 26 deletions.
31 changes: 27 additions & 4 deletions config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,7 @@ module MOM_surface_forcing_gfdl
!! gustiness calculations. Values below 20190101 recover the answers
!! from the end of 2018, while higher values use a simpler expression
!! to calculate gustiness.
logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the
logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the
!! gustless wind friction velocity.
logical :: check_no_land_fluxes !< Return warning if IOB flux over land is non-zero

Expand Down Expand Up @@ -284,7 +284,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
! flux type has been used.
if (fluxes%dt_buoy_accum < 0) then
call allocate_forcing_type(G, fluxes, water=.true., heat=.true., ustar=.not.CS%nonBous, press=.true., &
fix_accum_bug=CS%fix_ustar_gustless_bug, tau_mag=CS%nonBous)
fix_accum_bug=.not.CS%ustar_gustless_bug, tau_mag=CS%nonBous)

call safe_alloc_ptr(fluxes%sw_vis_dir,isd,ied,jsd,jed)
call safe_alloc_ptr(fluxes%sw_vis_dif,isd,ied,jsd,jed)
Expand Down Expand Up @@ -1298,6 +1298,8 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, wind_stagger)
logical :: new_sim ! False if this simulation was started from a restart file
! or other equivalent files.
logical :: iceberg_flux_diags ! If true, diagnostics of fluxes from icebergs are available.
logical :: fix_ustar_gustless_bug ! If false, include a bug using an older run-time parameter.
logical :: test_value ! This is used to determine whether a logical parameter is being set actively.
integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags.
type(time_type) :: Time_frc
type(directories) :: dirs ! A structure containing relevant directory paths and input filenames.
Expand Down Expand Up @@ -1611,9 +1613,30 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, wind_stagger)
"of 2018, while higher values use a simpler expression to calculate gustiness.", &
default=default_answer_date)

call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, &
call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false., do_not_log=.true.)
! This is used to test whether USTAR_GUSTLESS_BUG is being actively set.
call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.)
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, &
"If true correct a bug in the time-averaging of the gustless wind friction velocity", &
default=.true.)
default=.true., do_not_log=.true.)
if (test_value .eqv. CS%ustar_gustless_bug) then
! USTAR_GUSTLESS_BUG is being actively set, and should not be changed.
if ((.not.fix_ustar_gustless_bug) .and. (.not.CS%ustar_gustless_bug)) &
call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//&
"with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//&
"parameter and should be removed.")
else
CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug
if (.not.fix_ustar_gustless_bug) &
call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//&
"Use USTAR_GUSTLESS_BUG = True instead (it has the opposite sense).")
endif
call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false.)


! See whether sufficiently thick sea ice should be treated as rigid.
call get_param(param_file, mdl, "USE_RIGID_SEA_ICE", CS%rigid_sea_ice, &
Expand Down
37 changes: 29 additions & 8 deletions config_src/drivers/STALE_mct_cap/mom_surface_forcing_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module MOM_surface_forcing_mct
use MOM_domains, only : AGRID, BGRID_NE, CGRID_NE, To_All
use MOM_domains, only : To_North, To_East, Omit_Corners
use MOM_error_handler, only : MOM_error, WARNING, FATAL, is_root_pe, MOM_mesg
use MOM_file_parser, only : get_param, log_version, param_file_type
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_forcing_type, only : forcing, mech_forcing
use MOM_forcing_type, only : forcing_diags, mech_forcing_diags, register_forcing_type_diags
use MOM_forcing_type, only : allocate_forcing_type, deallocate_forcing_type
Expand Down Expand Up @@ -117,7 +117,7 @@ module MOM_surface_forcing_mct
real :: max_delta_srestore !< maximum delta salinity used for restoring [S ~> ppt]
real :: max_delta_trestore !< maximum delta sst used for restoring [C ~> degC]
real, pointer, dimension(:,:) :: basin_mask => NULL() !< mask for SSS restoring by basin
logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the
logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the
!! gustless wind friction velocity.
type(diag_ctrl), pointer :: diag !< structure to regulate diagnostic output timing
character(len=200) :: inputdir !< directory where NetCDF input files are
Expand Down Expand Up @@ -276,7 +276,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
! flux type has been used.
if (fluxes%dt_buoy_accum < 0) then
call allocate_forcing_type(G, fluxes, water=.true., heat=.true., ustar=.true., &
press=.true., fix_accum_bug=CS%fix_ustar_gustless_bug, tau_mag=.true.)
press=.true., fix_accum_bug=.not.CS%ustar_gustless_bug, tau_mag=.true.)

call safe_alloc_ptr(fluxes%sw_vis_dir,isd,ied,jsd,jed)
call safe_alloc_ptr(fluxes%sw_vis_dif,isd,ied,jsd,jed)
Expand Down Expand Up @@ -1025,11 +1025,11 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
! Local variables
real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1].
type(directories) :: dirs
logical :: new_sim, iceberg_flux_diags
logical :: new_sim, iceberg_flux_diags, fix_ustar_gustless_bug, test_value
type(time_type) :: Time_frc
character(len=200) :: TideAmp_file, gust_file, salt_file, temp_file ! Input file names.
! This include declares and sets the variable "version".
#include "version_variable.h"
! This include declares and sets the variable "version".
# include "version_variable.h"
character(len=40) :: mdl = "MOM_surface_forcing_mct" ! This module's name.
character(len=48) :: stagger
character(len=48) :: flnam
Expand Down Expand Up @@ -1257,9 +1257,30 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
call MOM_read_data(gust_file, 'gustiness', CS%gust, G%domain, timelevel=1, &
scale=US%kg_m3_to_R*US%m_s_to_L_T**2*US%L_to_Z) ! units in file should be Pa
endif
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, &

call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false., do_not_log=.true.)
! This is used to test whether USTAR_GUSTLESS_BUG is being actively set.
call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.)
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, &
"If true correct a bug in the time-averaging of the gustless wind friction velocity", &
default=.true.)
default=.true., do_not_log=.true.)
if (test_value .eqv. CS%ustar_gustless_bug) then
! USTAR_GUSTLESS_BUG is being actively set, and should not be changed.
if ((.not.fix_ustar_gustless_bug) .and. (.not.CS%ustar_gustless_bug)) &
call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//&
"with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//&
"parameter and should be removed.")
else
CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug
if (.not.fix_ustar_gustless_bug) &
call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//&
"Use USTAR_GUSTLESS_BUG = True instead (it has the opposite sense).")
endif
call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false.)

! See whether sufficiently thick sea ice should be treated as rigid.
call get_param(param_file, mdl, "USE_RIGID_SEA_ICE", CS%rigid_sea_ice, &
Expand Down
37 changes: 29 additions & 8 deletions config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ module MOM_surface_forcing_nuopc
use MOM_domains, only : AGRID, BGRID_NE, CGRID_NE, To_All
use MOM_domains, only : To_North, To_East, Omit_Corners
use MOM_error_handler, only : MOM_error, WARNING, FATAL, is_root_pe, MOM_mesg
use MOM_file_parser, only : get_param, log_version, param_file_type
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_forcing_type, only : forcing, mech_forcing
use MOM_forcing_type, only : forcing_diags, mech_forcing_diags, register_forcing_type_diags
use MOM_forcing_type, only : allocate_forcing_type, deallocate_forcing_type
Expand Down Expand Up @@ -124,7 +124,7 @@ module MOM_surface_forcing_nuopc
real :: max_delta_srestore !< maximum delta salinity used for restoring [S ~> ppt]
real :: max_delta_trestore !< maximum delta sst used for restoring [C ~> degC]
real, pointer, dimension(:,:) :: basin_mask => NULL() !< mask for SSS restoring by basin
logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the
logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the
!! gustless wind friction velocity.

type(diag_ctrl), pointer :: diag !< structure to regulate diagnostic output timing
Expand Down Expand Up @@ -296,7 +296,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
! flux type has been used.
if (fluxes%dt_buoy_accum < 0) then
call allocate_forcing_type(G, fluxes, water=.true., heat=.true., ustar=.true., &
press=.true., fix_accum_bug=CS%fix_ustar_gustless_bug, &
press=.true., fix_accum_bug=.not.CS%ustar_gustless_bug, &
cfc=CS%use_CFC, hevap=CS%enthalpy_cpl, tau_mag=.true.)
!call safe_alloc_ptr(fluxes%omega_w2x,isd,ied,jsd,jed)

Expand Down Expand Up @@ -1103,11 +1103,11 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
! Local variables
real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1].
type(directories) :: dirs
logical :: new_sim, iceberg_flux_diags
logical :: new_sim, iceberg_flux_diags, fix_ustar_gustless_bug, test_value
type(time_type) :: Time_frc
character(len=200) :: TideAmp_file, gust_file, salt_file, temp_file ! Input file names.
! This include declares and sets the variable "version".
#include "version_variable.h"
! This include declares and sets the variable "version".
# include "version_variable.h"
character(len=40) :: mdl = "MOM_surface_forcing_nuopc" ! This module's name.
character(len=48) :: stagger
character(len=48) :: flnam
Expand Down Expand Up @@ -1342,9 +1342,30 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
call MOM_read_data(gust_file, 'gustiness', CS%gust, G%domain, timelevel=1, &
scale=US%kg_m3_to_R*US%m_s_to_L_T**2*US%L_to_Z) ! units in file should be Pa
endif
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, &

call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false., do_not_log=.true.)
! This is used to test whether USTAR_GUSTLESS_BUG is being actively set.
call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.)
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, &
"If true correct a bug in the time-averaging of the gustless wind friction velocity", &
default=.true.)
default=.true., do_not_log=.true.)
if (test_value .eqv. CS%ustar_gustless_bug) then
! USTAR_GUSTLESS_BUG is being actively set, and should not be changed.
if ((.not.fix_ustar_gustless_bug) .and. (.not.CS%ustar_gustless_bug)) &
call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//&
"with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//&
"parameter and should be removed.")
else
CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug
if (.not.fix_ustar_gustless_bug) &
call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//&
"Use USTAR_GUSTLESS_BUG = True instead (it has the opposite sense).")
endif
call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false.)

! See whether sufficiently thick sea ice should be treated as rigid.
call get_param(param_file, mdl, "USE_RIGID_SEA_ICE", CS%rigid_sea_ice, &
Expand Down
36 changes: 30 additions & 6 deletions config_src/drivers/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ module MOM_surface_forcing
use MOM_domains, only : fill_symmetric_edges, CGRID_NE
use MOM_error_handler, only : MOM_error, FATAL, WARNING, MOM_mesg, is_root_pe
use MOM_error_handler, only : callTree_enter, callTree_leave
use MOM_file_parser, only : get_param, log_version, param_file_type
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_string_functions, only : uppercase
use MOM_forcing_type, only : forcing, mech_forcing
use MOM_forcing_type, only : set_net_mass_forcing, copy_common_forcing_fields
Expand Down Expand Up @@ -116,8 +116,8 @@ module MOM_surface_forcing
!! Dates before 20190101 use original answers.
!! Dates after 20190101 use a form of the gyre wind stresses that are
!! rotationally invariant and more likely to be the same between compilers.
logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the
!! gustless wind friction velocity.
logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the
!! gustless wind friction velocity.
! if WIND_CONFIG=='scurves' then use the following to define a piecewise scurve profile
real :: scurves_ydata(20) = 90. !< Latitudes of scurve nodes [degreesN]
real :: scurves_taux(20) = 0. !< Zonal wind stress values at scurve nodes [R L Z T-2 ~> Pa]
Expand Down Expand Up @@ -256,7 +256,7 @@ subroutine set_forcing(sfc_state, forces, fluxes, day_start, day_interval, G, US
call allocate_mech_forcing(G, forces, stress=.true., ustar=.not.CS%nonBous, press=.true., tau_mag=CS%nonBous)

call allocate_forcing_type(G, fluxes, ustar=.not.CS%nonBous, tau_mag=CS%nonBous, &
fix_accum_bug=CS%fix_ustar_gustless_bug)
fix_accum_bug=.not.CS%ustar_gustless_bug)
if (trim(CS%buoy_config) /= "NONE") then
if ( CS%use_temperature ) then
call allocate_forcing_type(G, fluxes, water=.true., heat=.true., press=.true.)
Expand Down Expand Up @@ -1582,6 +1582,8 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, tracer_flow_C
real :: flux_const_default ! The unscaled value of FLUXCONST [m day-1]
logical :: Boussinesq ! If true, this run is fully Boussinesq
logical :: semi_Boussinesq ! If true, this run is partially non-Boussinesq
logical :: fix_ustar_gustless_bug ! If false, include a bug using an older run-time parameter.
logical :: test_value ! This is used to determine whether a logical parameter is being set actively.
integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags.
character(len=40) :: mdl = "MOM_surface_forcing" ! This module's name.
character(len=200) :: filename, gust_file ! The name of the gustiness input file.
Expand Down Expand Up @@ -1935,9 +1937,31 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, tracer_flow_C
call get_param(param_file, mdl, "GUST_CONST", CS%gust_const, &
"The background gustiness in the winds.", &
units="Pa", default=0.0, scale=US%Pa_to_RLZ_T2)
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, &

call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false., do_not_log=.true.)
! This is used to test whether USTAR_GUSTLESS_BUG is being actively set.
call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.)
call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, &
"If true correct a bug in the time-averaging of the gustless wind friction velocity", &
default=.true.)
default=.true., do_not_log=.true.)
if (test_value .eqv. CS%ustar_gustless_bug) then
! USTAR_GUSTLESS_BUG is being actively set, and should not be changed.
if ((.not.fix_ustar_gustless_bug) .and. (.not.CS%ustar_gustless_bug)) &
call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//&
"with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//&
"parameter and should be removed.")
else
CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug
if (.not.fix_ustar_gustless_bug) &
call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//&
"Use USTAR_GUSTLESS_BUG = True instead (it has the opposite sense).")
endif
call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, &
"If true include a bug in the time-averaging of the gustless wind friction velocity", &
default=.false.)

call get_param(param_file, mdl, "READ_GUST_2D", CS%read_gust_2d, &
"If true, use a 2-dimensional gustiness supplied from "//&
"an input file", default=.false.)
Expand Down

0 comments on commit 7b97002

Please sign in to comment.