Skip to content

Commit 6084824

Browse files
committed
Add INTERFACE_FILTER_DT_BUG
A new parameter, INTERFACE_FILTER_DT_BUG, is added to fix two bugs in the time interval passed to interface_filter and to thickness_diffuse. This parameter has no effect, and is not read or logged, when THICKNESSDIFFUSE_FIRST is true and DT_TRACER_ADVECT = DT_THERMO or when both THICKNESSDIFFUSE_FIRST and APPLY_INTERFACE_FILTER are false. Its default is false which will change answers in the rare existing cases with the bug. In such cases, the original answers can be restored by setting INTERFACE_FILTER_DT_BUG to true.
1 parent 70dde77 commit 6084824

File tree

1 file changed

+45
-22
lines changed

1 file changed

+45
-22
lines changed

src/core/MOM.F90

Lines changed: 45 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -302,6 +302,8 @@ module MOM
302302
!! after any calls to thickness_diffuse.
303303
logical :: thickness_diffuse !< If true, diffuse interface height w/ a diffusivity KHTH.
304304
logical :: thickness_diffuse_first !< If true, diffuse thickness before dynamics.
305+
logical :: interface_filter_dt_bug !< If true, uses the wrong time interval in
306+
!! calls to interface_filter and thickness_diffuse.
305307
logical :: mixedlayer_restrat !< If true, use submesoscale mixed layer restratifying scheme.
306308
logical :: useMEKE !< If true, call the MEKE parameterization.
307309
logical :: use_stochastic_EOS !< If true, use the stochastic EOS parameterizations.
@@ -550,7 +552,7 @@ subroutine step_MOM(forces_in, fluxes_in, sfc_state, Time_start, time_int_in, CS
550552
real :: dtdia ! time step for diabatic processes [T ~> s]
551553
real :: dt_tr_adv ! time step for tracer advection [T ~> s]
552554
real :: dt_therm ! a limited and quantized version of CS%dt_therm [T ~> s]
553-
real :: dt_therm_here ! a further limited value of dt_therm [T ~> s]
555+
real :: dt_tradv_here ! a further limited value of dt_tr_adv [T ~> s]
554556

555557
real :: wt_end, wt_beg ! Fractional weights of the future pressure at the end
556558
! and beginning of the current time step [nondim]
@@ -914,9 +916,15 @@ subroutine step_MOM(forces_in, fluxes_in, sfc_state, Time_start, time_int_in, CS
914916
enddo ; enddo ; enddo
915917
endif
916918

917-
dt_therm_here = dt_therm
918-
if (do_thermo .and. do_dyn .and. .not.thermo_does_span_coupling) &
919-
dt_therm_here = dt*min(ntstep, n_max-n+1)
919+
if (CS%interface_filter_dt_bug) then
920+
dt_tradv_here = dt_therm
921+
if (do_thermo .and. do_dyn .and. .not.thermo_does_span_coupling) &
922+
dt_tradv_here = dt*min(ntstep, n_max-n+1)
923+
else
924+
dt_tradv_here = dt_tr_adv
925+
if (do_thermo .and. do_dyn .and. .not.tradv_does_span_coupling) &
926+
dt_tradv_here = dt*min(ntstep, n_max-n+1)
927+
endif
920928

921929
! Indicate whether the bottom boundary layer properties need to be
922930
! recalculated, and if so for how long an interval they are valid.
@@ -943,7 +951,7 @@ subroutine step_MOM(forces_in, fluxes_in, sfc_state, Time_start, time_int_in, CS
943951
if (associated(CS%HA_CSp)) call HA_accum_FtF(Time_Local, CS%HA_CSp)
944952

945953
call step_MOM_dynamics(forces, CS%p_surf_begin, CS%p_surf_end, dt, &
946-
dt_therm_here, bbl_time_int, CS, &
954+
dt_tradv_here, bbl_time_int, CS, &
947955
Time_local, Waves=Waves)
948956

949957
!===========================================================================
@@ -1149,7 +1157,7 @@ subroutine step_MOM(forces_in, fluxes_in, sfc_state, Time_start, time_int_in, CS
11491157
end subroutine step_MOM
11501158

11511159
!> Time step the ocean dynamics, including the momentum and continuity equations
1152-
subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
1160+
subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_tr_adv, &
11531161
bbl_time_int, CS, Time_local, Waves)
11541162
type(mech_forcing), intent(in) :: forces !< A structure with the driving mechanical forces
11551163
real, dimension(:,:), pointer :: p_surf_begin !< A pointer (perhaps NULL) to the surface
@@ -1159,7 +1167,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
11591167
!! pressure at the end of this dynamic step,
11601168
!! intent in [R L2 T-2 ~> Pa].
11611169
real, intent(in) :: dt !< time interval covered by this call [T ~> s].
1162-
real, intent(in) :: dt_thermo !< time interval covered by any updates that may
1170+
real, intent(in) :: dt_tr_adv !< time interval covered by any updates that may
11631171
!! span multiple dynamics steps [T ~> s].
11641172
real, intent(in) :: bbl_time_int !< time interval over which updates to the
11651173
!! bottom boundary layer properties will apply [T ~> s],
@@ -1211,12 +1219,12 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
12111219
if ((CS%t_dyn_rel_adv == 0.0) .and. CS%thickness_diffuse_first .and. &
12121220
(CS%thickness_diffuse .or. CS%interface_filter)) then
12131221

1214-
call enable_averages(dt_thermo, Time_local+real_to_time(US%T_to_s*(dt_thermo-dt)), CS%diag)
1222+
call enable_averages(dt_tr_adv, Time_local+real_to_time(US%T_to_s*(dt_tr_adv-dt)), CS%diag)
12151223
if (CS%thickness_diffuse) then
12161224
call cpu_clock_begin(id_clock_thick_diff)
12171225
if (CS%VarMix%use_variable_mixing) &
12181226
call calc_slope_functions(h, CS%tv, dt, G, GV, US, CS%VarMix, OBC=CS%OBC)
1219-
call thickness_diffuse(h, CS%uhtr, CS%vhtr, CS%tv, dt_thermo, G, GV, US, &
1227+
call thickness_diffuse(h, CS%uhtr, CS%vhtr, CS%tv, dt_tr_adv, G, GV, US, &
12201228
CS%MEKE, CS%VarMix, CS%CDp, CS%thickness_diffuse_CSp)
12211229
call cpu_clock_end(id_clock_thick_diff)
12221230
call pass_var(h, G%Domain, clock=id_clock_pass, halo=max(2,CS%cont_stencil))
@@ -1227,7 +1235,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
12271235
if (allocated(CS%tv%SpV_avg)) call pass_var(CS%tv%SpV_avg, G%Domain, clock=id_clock_pass)
12281236
CS%tv%valid_SpV_halo = min(G%Domain%nihalo, G%Domain%njhalo)
12291237
call cpu_clock_begin(id_clock_int_filter)
1230-
call interface_filter(h, CS%uhtr, CS%vhtr, CS%tv, dt_thermo, G, GV, US, &
1238+
call interface_filter(h, CS%uhtr, CS%vhtr, CS%tv, dt_tr_adv, G, GV, US, &
12311239
CS%CDp, CS%interface_filter_CSp)
12321240
call cpu_clock_end(id_clock_int_filter)
12331241
call pass_var(h, G%Domain, clock=id_clock_pass, halo=max(2,CS%cont_stencil))
@@ -1379,8 +1387,13 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
13791387
if (allocated(CS%tv%SpV_avg)) call pass_var(CS%tv%SpV_avg, G%Domain, clock=id_clock_pass)
13801388
CS%tv%valid_SpV_halo = min(G%Domain%nihalo, G%Domain%njhalo)
13811389
call cpu_clock_begin(id_clock_int_filter)
1382-
call interface_filter(h, CS%uhtr, CS%vhtr, CS%tv, dt_thermo, G, GV, US, &
1383-
CS%CDp, CS%interface_filter_CSp)
1390+
if (CS%interface_filter_dt_bug) then
1391+
call interface_filter(h, CS%uhtr, CS%vhtr, CS%tv, dt_tr_adv, G, GV, US, &
1392+
CS%CDp, CS%interface_filter_CSp)
1393+
else
1394+
call interface_filter(h, CS%uhtr, CS%vhtr, CS%tv, dt, G, GV, US, &
1395+
CS%CDp, CS%interface_filter_CSp)
1396+
endif
13841397
call cpu_clock_end(id_clock_int_filter)
13851398
call pass_var(h, G%Domain, clock=id_clock_pass, halo=max(2,CS%cont_stencil))
13861399
if (showCallTree) call callTree_waypoint("finished interface_filter (step_MOM)")
@@ -2434,16 +2447,6 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
24342447
"BULKMIXEDLAYER can not be used with USE_REGRIDDING. "//&
24352448
"The default is influenced by ENABLE_THERMODYNAMICS.", &
24362449
default=use_temperature .and. .not.CS%use_ALE_algorithm)
2437-
call get_param(param_file, "MOM", "THICKNESSDIFFUSE", CS%thickness_diffuse, &
2438-
"If true, isopycnal surfaces are diffused with a Laplacian "//&
2439-
"coefficient of KHTH.", default=.false.)
2440-
call get_param(param_file, "MOM", "APPLY_INTERFACE_FILTER", CS%interface_filter, &
2441-
"If true, model interface heights are subjected to a grid-scale "//&
2442-
"dependent spatial smoothing, often with biharmonic filter.", default=.false.)
2443-
call get_param(param_file, "MOM", "THICKNESSDIFFUSE_FIRST", CS%thickness_diffuse_first, &
2444-
"If true, do thickness diffusion or interface height smoothing before dynamics. "//&
2445-
"This is only used if THICKNESSDIFFUSE or APPLY_INTERFACE_FILTER is true.", &
2446-
default=.false., do_not_log=.not.(CS%thickness_diffuse.or.CS%interface_filter))
24472450
call get_param(param_file, "MOM", "USE_POROUS_BARRIER", CS%use_porbar, &
24482451
"If true, use porous barrier to constrain the widths "//&
24492452
"and face areas at the edges of the grid cells. ", &
@@ -2499,6 +2502,26 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
24992502
if ( CS%diabatic_first .and. (CS%dt_tr_adv /= CS%dt_therm) ) then
25002503
call MOM_error(FATAL,"MOM: If using DIABATIC_FIRST, DT_TRACER_ADVECT must equal DT_THERM.")
25012504
endif
2505+
call get_param(param_file, "MOM", "THICKNESSDIFFUSE", CS%thickness_diffuse, &
2506+
"If true, isopycnal surfaces are diffused with a Laplacian "//&
2507+
"coefficient of KHTH.", default=.false.)
2508+
call get_param(param_file, "MOM", "APPLY_INTERFACE_FILTER", CS%interface_filter, &
2509+
"If true, model interface heights are subjected to a grid-scale "//&
2510+
"dependent spatial smoothing, often with biharmonic filter.", default=.false.)
2511+
call get_param(param_file, "MOM", "THICKNESSDIFFUSE_FIRST", CS%thickness_diffuse_first, &
2512+
"If true, do thickness diffusion or interface height smoothing before dynamics. "//&
2513+
"This is only used if THICKNESSDIFFUSE or APPLY_INTERFACE_FILTER is true.", &
2514+
default=.false., do_not_log=.not.(CS%thickness_diffuse.or.CS%interface_filter))
2515+
CS%interface_filter_dt_bug = .false.
2516+
if ((.not.CS%thickness_diffuse_first .and. CS%interface_filter) .or. &
2517+
(CS%thickness_diffuse_first .and. (CS%thickness_diffuse .or. CS%interface_filter) &
2518+
.and. (CS%dt_tr_adv /= CS%dt_therm))) then
2519+
call get_param(param_file, "MOM", "INTERFACE_FILTER_DT_BUG", CS%interface_filter_dt_bug, &
2520+
"If true, uses the wrong time interval in calls to interface_filter "//&
2521+
"and thickness_diffuse. Has no effect when THICKNESSDIFFUSE_FIRST is "//&
2522+
"true and DT_TRACER_ADVECT = DT_THERMO or when THICKNESSDIFFUSE_FIRST "//&
2523+
"is false and APPLY_INTERFACE_FILTER is false. ", default=.false.)
2524+
endif
25022525

25032526
if (bulkmixedlayer) then
25042527
CS%Hmix = -1.0 ; CS%Hmix_UV = -1.0

0 commit comments

Comments
 (0)