Skip to content

Commit

Permalink
Add KPP OBLdepth to restart file
Browse files Browse the repository at this point in the history
Created a register_KPP_restarts() subroutine that allocates KPP_CS and also
memory for KPP's boundary layer depth, and then adds the BLD to restarts if
FPMix is turned on. We really only need BLD in the restart if FPMIX=True and
DIABATIC_FIRST=False, but I think basing whether or not to write to the restart
file solely on FPMIX is okay
  • Loading branch information
mnlevy1981 committed Oct 28, 2024
1 parent ad7cf38 commit 67e7e24
Show file tree
Hide file tree
Showing 3 changed files with 44 additions and 17 deletions.
2 changes: 1 addition & 1 deletion src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2895,7 +2895,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
endif

if (.not. CS%adiabatic) then
call register_diabatic_restarts(G, US, param_file, CS%int_tide_CSp, restart_CSp)
call register_diabatic_restarts(G, US, param_file, CS%int_tide_CSp, restart_CSp, CS%diabatic_CSp)
endif

call callTree_waypoint("restart registration complete (initialize_MOM)")
Expand Down
36 changes: 30 additions & 6 deletions src/parameterizations/vertical/MOM_CVMix_KPP.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ module MOM_CVMix_KPP
use MOM_file_parser, only : openParameterBlock, closeParameterBlock
use MOM_grid, only : ocean_grid_type, isPointInCell
use MOM_interface_heights, only : thickness_to_dz
use MOM_restart, only : MOM_restart_CS, register_restart_field
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : thermo_var_ptrs
use MOM_verticalGrid, only : verticalGrid_type
Expand All @@ -36,6 +37,7 @@ module MOM_CVMix_KPP

#include "MOM_memory.h"

public :: register_KPP_restarts
public :: KPP_init
public :: KPP_compute_BLD
public :: KPP_calculate
Expand Down Expand Up @@ -152,7 +154,7 @@ module MOM_CVMix_KPP
!>@}

! Diagnostics arrays
real, allocatable, dimension(:,:) :: OBLdepth !< Depth (positive) of ocean boundary layer (OBL) [Z ~> m]
real, pointer, dimension(:,:) :: OBLdepth !< Depth (positive) of ocean boundary layer (OBL) [Z ~> m]
real, allocatable, dimension(:,:) :: OBLdepth_original !< Depth (positive) of OBL [Z ~> m] without smoothing
real, allocatable, dimension(:,:) :: StokesParXI !< Stokes similarity parameter
real, allocatable, dimension(:,:) :: Lam2 !< La^(-2) = Ustk0/u*
Expand Down Expand Up @@ -188,6 +190,33 @@ module MOM_CVMix_KPP

contains

!> Routine to register restarts, pass-through to children modules
subroutine register_KPP_restarts(G, param_file, restart_CSp, CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(MOM_restart_CS), pointer :: restart_CSp !< MOM restart control structure
type(KPP_CS), pointer :: CS !< module control structure

character(len=40) :: mdl = 'MOM_CVMix_KPP' !< name of this module
logical :: use_kpp, fpmix

if (associated(CS)) call MOM_error(FATAL, 'MOM_CVMix_KPP, register_KPP_restarts: '// &
'Control structure has already been initialized')
call get_param(param_file, mdl, "USE_KPP", use_kpp, default=.false., do_not_log=.true.)
! Forego remainder of initialization if not using this scheme
if (.not. use_kpp) return
allocate(CS)

allocate(CS%OBLdepth(SZI_(G),SZJ_(G)), source=0.0)

! FPMIX is needed to decide if boundary layer depth should be added to restart file
call get_param(param_file, '', "FPMIX", fpmix, &
"If true, add non-local momentum flux increments and diffuse down the Eulerian gradient.", &
default=.false., do_not_log=.true.)
if (fpmix) call register_restart_field(CS%OBLdepth, 'KPP_OBLdepth', .false., restart_CSp)

end subroutine register_KPP_restarts

!> Initialize the CVMix KPP module and set up diagnostics
!! Returns True if KPP is to be used, False otherwise.
logical function KPP_init(paramFile, G, GV, US, diag, Time, CS, passive)
Expand All @@ -213,9 +242,6 @@ logical function KPP_init(paramFile, G, GV, US, diag, Time, CS, passive)
logical :: CS_IS_ONE=.false. !< Logical for setting Cs based on Non-local
logical :: lnoDGat1=.false. !< True => G'(1) = 0 (shape function)
!! False => compute G'(1) as in LMD94
if (associated(CS)) call MOM_error(FATAL, 'MOM_CVMix_KPP, KPP_init: '// &
'Control structure has already been initialized')

! Read parameters
call get_param(paramFile, mdl, "USE_KPP", KPP_init, default=.false., do_not_log=.true.)
call log_version(paramFile, mdl, version, 'This is the MOM wrapper to CVMix:KPP\n' // &
Expand All @@ -226,7 +252,6 @@ logical function KPP_init(paramFile, G, GV, US, diag, Time, CS, passive)
default=.false.)
! Forego remainder of initialization if not using this scheme
if (.not. KPP_init) return
allocate(CS)

call get_param(paramFile, mdl, "DEFAULT_ANSWER_DATE", default_answer_date, &
"This sets the default value for the various _ANSWER_DATE parameters.", &
Expand Down Expand Up @@ -599,7 +624,6 @@ logical function KPP_init(paramFile, G, GV, US, diag, Time, CS, passive)
'Surface-layer Langmuir number computed in [CVMix] KPP','nondim')

allocate( CS%N( SZI_(G), SZJ_(G), SZK_(GV)+1 ), source=0. )
allocate( CS%OBLdepth( SZI_(G), SZJ_(G) ), source=0. )
allocate( CS%StokesParXI( SZI_(G), SZJ_(G) ), source=0. )
allocate( CS%Lam2 ( SZI_(G), SZJ_(G) ), source=0. )
allocate( CS%kOBL( SZI_(G), SZJ_(G) ), source=0. )
Expand Down
23 changes: 13 additions & 10 deletions src/parameterizations/vertical/MOM_diabatic_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ module MOM_diabatic_driver
use MOM_internal_tides, only : internal_tides_init, internal_tides_end, int_tide_CS
use MOM_kappa_shear, only : kappa_shear_is_used
use MOM_CVMix_KPP, only : KPP_CS, KPP_init, KPP_compute_BLD, KPP_calculate
use MOM_CVMix_KPP, only : KPP_end, KPP_get_BLD
use MOM_CVMix_KPP, only : KPP_end, KPP_get_BLD, register_KPP_restarts
use MOM_CVMix_KPP, only : KPP_NonLocalTransport_temp, KPP_NonLocalTransport_saln
use MOM_oda_incupd, only : apply_oda_incupd, oda_incupd_CS
use MOM_opacity, only : opacity_init, opacity_end, opacity_CS
Expand Down Expand Up @@ -3026,14 +3026,6 @@ subroutine diabatic_driver_init(Time, G, GV, US, param_file, useALEalgorithm, di
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = GV%ke
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB

if (associated(CS)) then
call MOM_error(WARNING, "diabatic_driver_init called with an "// &
"associated control structure.")
return
else
allocate(CS)
endif

CS%initialized = .true.

CS%diag => diag
Expand Down Expand Up @@ -3568,15 +3560,24 @@ subroutine diabatic_driver_init(Time, G, GV, US, param_file, useALEalgorithm, di
end subroutine diabatic_driver_init

!> Routine to register restarts, pass-through to children modules
subroutine register_diabatic_restarts(G, US, param_file, int_tide_CSp, restart_CSp)
subroutine register_diabatic_restarts(G, US, param_file, int_tide_CSp, restart_CSp, CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(int_tide_CS), pointer :: int_tide_CSp !< Internal tide control structure
type(MOM_restart_CS), pointer :: restart_CSp !< MOM restart control structure
type(diabatic_CS), pointer :: CS !< module control structure

logical :: use_int_tides

if (associated(CS)) then
call MOM_error(WARNING, "diabatic_driver_init called with an "// &
"associated control structure.")
return
else
allocate(CS)
endif

use_int_tides=.false.

call read_param(param_file, "INTERNAL_TIDES", use_int_tides)
Expand All @@ -3585,6 +3586,8 @@ subroutine register_diabatic_restarts(G, US, param_file, int_tide_CSp, restart_C
call register_int_tide_restarts(G, US, param_file, int_tide_CSp, restart_CSp)
endif

call register_KPP_restarts(G, param_file, restart_CSp, CS%KPP_CSp)

end subroutine register_diabatic_restarts

!> Routine to close the diabatic driver module
Expand Down

0 comments on commit 67e7e24

Please sign in to comment.