MOM6
mom_dynamics_split_rk2 Module Reference

Detailed Description

Time step the adiabatic dynamic core of MOM using RK2 method.

This file time steps the adiabatic dynamic core by splitting between baroclinic and barotropic modes. It uses a pseudo-second order Runge-Kutta time stepping scheme for the baroclinic momentum equation and a forward-backward coupling between the baroclinic momentum and continuity equations. This split time-stepping scheme is described in detail in Hallberg (JCP, 1997). Additional issues related to exact tracer conservation and how to ensure consistency between the barotropic and layered estimates of the free surface height are described in Hallberg and Adcroft (Ocean Modelling, 2009). This was the time stepping code that is used for most GOLD applications, including GFDL's ESM2G Earth system model, and all of the examples provided with the MOM code (although several of these solutions are routinely verified by comparison with the slower unsplit schemes).

The subroutine step_MOM_dyn_split_RK2 actually does the time stepping, while register_restarts_dyn_split_RK2 sets the fields that are found in a full restart file with this scheme, and initialize_dyn_split_RK2 initializes the cpu clocks that are used in this module. For largely historical reasons, this module does not have its own control structure, but shares the same control structure with MOM.F90 and the other MOM_dynamics_... modules.

Data Types

type  mom_dyn_split_rk2_cs
 Module control structure. More...
 

Functions/Subroutines

subroutine, public step_mom_dyn_split_rk2 (u, v, h, tv, visc, Time_local, dt, fluxes, p_surf_begin, p_surf_end, dt_since_flux, dt_therm, uh, vh, uhtr, vhtr, eta_av, G, GV, CS, calc_dtbt, VarMix, MEKE)
 RK2 splitting for time stepping MOM adiabatic dynamics. More...
 
subroutine, public register_restarts_dyn_split_rk2 (HI, GV, param_file, CS, restart_CS, uh, vh)
 This subroutine sets up any auxiliary restart variables that are specific to the unsplit time stepping scheme. All variables registered here should have the ability to be recreated if they are not present in a restart file. More...
 
subroutine, public initialize_dyn_split_rk2 (u, v, h, uh, vh, eta, Time, G, GV, param_file, diag, CS, restart_CS, dt, Accel_diag, Cont_diag, MIS, VarMix, MEKE, OBC, update_OBC_CSp, ALE_CSp, setVisc_CSp, visc, dirs, ntrunc)
 This subroutine initializes all of the variables that are used by this dynamic core, including diagnostics and the cpu clocks. More...
 
subroutine, public end_dyn_split_rk2 (CS)
 Close the dyn_split_RK2 module. More...
 

Variables

integer id_clock_cor
 
integer id_clock_pres
 
integer id_clock_vertvisc
 
integer id_clock_horvisc
 
integer id_clock_mom_update
 
integer id_clock_continuity
 
integer id_clock_thick_diff
 
integer id_clock_btstep
 
integer id_clock_btcalc
 
integer id_clock_btforce
 
integer id_clock_pass
 
integer id_clock_pass_init
 

Function/Subroutine Documentation

◆ end_dyn_split_rk2()

subroutine, public mom_dynamics_split_rk2::end_dyn_split_rk2 ( type(mom_dyn_split_rk2_cs), pointer  CS)

Close the dyn_split_RK2 module.

Parameters
csmodule control structure

Definition at line 1159 of file MOM_dynamics_split_RK2.F90.

1159  type(mom_dyn_split_rk2_cs), pointer :: cs !< module control structure
1160 
1161  dealloc_(cs%diffu) ; dealloc_(cs%diffv)
1162  dealloc_(cs%CAu) ; dealloc_(cs%CAv)
1163  dealloc_(cs%PFu) ; dealloc_(cs%PFv)
1164 
1165  if (associated(cs%taux_bot)) deallocate(cs%taux_bot)
1166  if (associated(cs%tauy_bot)) deallocate(cs%tauy_bot)
1167  dealloc_(cs%uhbt) ; dealloc_(cs%vhbt)
1168  dealloc_(cs%u_accel_bt) ; dealloc_(cs%v_accel_bt)
1169  dealloc_(cs%visc_rem_u) ; dealloc_(cs%visc_rem_v)
1170 
1171  dealloc_(cs%eta) ; dealloc_(cs%eta_PF) ; dealloc_(cs%pbce)
1172  dealloc_(cs%h_av) ; dealloc_(cs%u_av) ; dealloc_(cs%v_av)
1173 
1174  call dealloc_bt_cont_type(cs%BT_cont)
1175 
1176  deallocate(cs)

◆ initialize_dyn_split_rk2()

subroutine, public mom_dynamics_split_rk2::initialize_dyn_split_rk2 ( real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(inout)  u,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(inout)  v,
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(inout)  h,
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(inout), target  uh,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(inout), target  vh,
real, dimension( g %isd: g %ied, g %jsd: g %jed), intent(inout)  eta,
type(time_type), intent(in), target  Time,
type(ocean_grid_type), intent(inout)  G,
type(verticalgrid_type), intent(in)  GV,
type(param_file_type), intent(in)  param_file,
type(diag_ctrl), intent(inout), target  diag,
type(mom_dyn_split_rk2_cs), pointer  CS,
type(mom_restart_cs), pointer  restart_CS,
real, intent(in)  dt,
type(accel_diag_ptrs), intent(inout), target  Accel_diag,
type(cont_diag_ptrs), intent(inout), target  Cont_diag,
type(ocean_internal_state), intent(inout)  MIS,
type(varmix_cs), pointer  VarMix,
type(meke_type), pointer  MEKE,
type(ocean_obc_type), pointer  OBC,
type(update_obc_cs), pointer  update_OBC_CSp,
type(ale_cs), pointer  ALE_CSp,
type(set_visc_cs), pointer  setVisc_CSp,
type(vertvisc_type), intent(inout)  visc,
type(directories), intent(in)  dirs,
integer, intent(inout), target  ntrunc 
)

This subroutine initializes all of the variables that are used by this dynamic core, including diagnostics and the cpu clocks.

Parameters
[in,out]gocean grid structure
[in]gvocean vertical grid structure
[in,out]uzonal velocity (m/s)
[in,out]vmerid velocity (m/s)
[in,out]hlayer thickness (m or kg/m2)
[in,out]uhzonal volume/mass transport (m3 s-1 or kg s-1)
[in,out]vhmerid volume/mass transport (m3 s-1 or kg s-1)
[in,out]etafree surface height or column mass (m or kg m-2)
[in]timecurrent model time
[in]param_fileparameter file for parsing
[in,out]diagto control diagnostics
csmodule control structure
restart_csrestart control structure
[in]dttime step (sec)
[in,out]accel_diagpoints to momentum equation terms for budget analysis
[in,out]cont_diagpoints to terms in continuity equation
[in,out]mis"MOM6 internal state" used to pass diagnostic pointers
varmixpoints to spatially variable viscosities
mekepoints to mesoscale eddy kinetic energy fields
obcpoints to OBC related fields
update_obc_csppoints to OBC update related fields
ale_csppoints to ALE control structure
setvisc_csppoints to the set_visc control structure.
[in,out]viscvertical viscosities, bottom drag, and related
[in]dirscontains directory paths
[in,out]ntruncA target for the variable that records the number of times the velocity is truncated (this should be 0).

Definition at line 927 of file MOM_dynamics_split_RK2.F90.

References id_clock_btcalc, id_clock_btforce, id_clock_btstep, id_clock_continuity, id_clock_cor, id_clock_horvisc, id_clock_mom_update, id_clock_pass, id_clock_pass_init, id_clock_pres, and id_clock_vertvisc.

927  type(ocean_grid_type), intent(inout) :: g !< ocean grid structure
928  type(verticalgrid_type), intent(in) :: gv !< ocean vertical grid structure
929  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(inout) :: u !< zonal velocity (m/s)
930  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(inout) :: v !< merid velocity (m/s)
931  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) , intent(inout) :: h !< layer thickness (m or kg/m2)
932  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target, intent(inout) :: uh !< zonal volume/mass transport (m3 s-1 or kg s-1)
933  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target, intent(inout) :: vh !< merid volume/mass transport (m3 s-1 or kg s-1)
934  real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: eta !< free surface height or column mass (m or kg m-2)
935  type(time_type), target, intent(in) :: time !< current model time
936  type(param_file_type), intent(in) :: param_file !< parameter file for parsing
937  type(diag_ctrl), target, intent(inout) :: diag !< to control diagnostics
938  type(mom_dyn_split_rk2_cs), pointer :: cs !< module control structure
939  type(mom_restart_cs), pointer :: restart_cs !< restart control structure
940  real, intent(in) :: dt !< time step (sec)
941  type(accel_diag_ptrs), target, intent(inout) :: accel_diag !< points to momentum equation terms for budget analysis
942  type(cont_diag_ptrs), target, intent(inout) :: cont_diag !< points to terms in continuity equation
943  type(ocean_internal_state), intent(inout) :: mis !< "MOM6 internal state" used to pass diagnostic pointers
944  type(varmix_cs), pointer :: varmix !< points to spatially variable viscosities
945  type(meke_type), pointer :: meke !< points to mesoscale eddy kinetic energy fields
946  type(ocean_obc_type), pointer :: obc !< points to OBC related fields
947  type(update_obc_cs), pointer :: update_obc_csp !< points to OBC update related fields
948  type(ale_cs), pointer :: ale_csp !< points to ALE control structure
949  type(set_visc_cs), pointer :: setvisc_csp !< points to the set_visc control structure.
950  type(vertvisc_type), intent(inout) :: visc !< vertical viscosities, bottom drag, and related
951  type(directories), intent(in) :: dirs !< contains directory paths
952  integer, target, intent(inout) :: ntrunc !< A target for the variable that records the number of times
953  !! the velocity is truncated (this should be 0).
954 
955  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_tmp
956  character(len=40) :: mdl = "MOM_dynamics_split_RK2" ! This module's name.
957  character(len=48) :: thickness_units, flux_units
958  type(group_pass_type) :: pass_h_tmp, pass_av_h_uvh
959  logical :: use_tides, debug_truncations
960 
961  integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz
962  integer :: isdb, iedb, jsdb, jedb
963  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
964  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
965  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
966 
967  if (.not.associated(cs)) call mom_error(fatal, &
968  "initialize_dyn_split_RK2 called with an unassociated control structure.")
969  if (cs%module_is_initialized) then
970  call mom_error(warning, "initialize_dyn_split_RK2 called with a control "// &
971  "structure that has already been initialized.")
972  return
973  endif
974  cs%module_is_initialized = .true.
975 
976  cs%diag => diag
977 
978  call get_param(param_file, mdl, "TIDES", use_tides, &
979  "If true, apply tidal momentum forcing.", default=.false.)
980  call get_param(param_file, mdl, "BE", cs%be, &
981  "If SPLIT is true, BE determines the relative weighting \n"//&
982  "of a 2nd-order Runga-Kutta baroclinic time stepping \n"//&
983  "scheme (0.5) and a backward Euler scheme (1) that is \n"//&
984  "used for the Coriolis and inertial terms. BE may be \n"//&
985  "from 0.5 to 1, but instability may occur near 0.5. \n"//&
986  "BE is also applicable if SPLIT is false and USE_RK2 \n"//&
987  "is true.", units="nondim", default=0.6)
988  call get_param(param_file, mdl, "BEGW", cs%begw, &
989  "If SPLIT is true, BEGW is a number from 0 to 1 that \n"//&
990  "controls the extent to which the treatment of gravity \n"//&
991  "waves is forward-backward (0) or simulated backward \n"//&
992  "Euler (1). 0 is almost always used.\n"//&
993  "If SPLIT is false and USE_RK2 is true, BEGW can be \n"//&
994  "between 0 and 0.5 to damp gravity waves.", &
995  units="nondim", default=0.0)
996 
997  call get_param(param_file, mdl, "SPLIT_BOTTOM_STRESS", cs%split_bottom_stress, &
998  "If true, provide the bottom stress calculated by the \n"//&
999  "vertical viscosity to the barotropic solver.", default=.false.)
1000  call get_param(param_file, mdl, "BT_USE_LAYER_FLUXES", cs%BT_use_layer_fluxes, &
1001  "If true, use the summed layered fluxes plus an \n"//&
1002  "adjustment due to the change in the barotropic velocity \n"//&
1003  "in the barotropic continuity equation.", default=.true.)
1004  call get_param(param_file, mdl, "DEBUG", cs%debug, &
1005  "If true, write out verbose debugging data.", default=.false.)
1006  call get_param(param_file, mdl, "DEBUG_TRUNCATIONS", debug_truncations, &
1007  default=.false.)
1008 
1009  allocate(cs%taux_bot(isdb:iedb,jsd:jed)) ; cs%taux_bot(:,:) = 0.0
1010  allocate(cs%tauy_bot(isd:ied,jsdb:jedb)) ; cs%tauy_bot(:,:) = 0.0
1011 
1012  alloc_(cs%uhbt(isdb:iedb,jsd:jed)) ; cs%uhbt(:,:) = 0.0
1013  alloc_(cs%vhbt(isd:ied,jsdb:jedb)) ; cs%vhbt(:,:) = 0.0
1014  alloc_(cs%visc_rem_u(isdb:iedb,jsd:jed,nz)) ; cs%visc_rem_u(:,:,:) = 0.0
1015  alloc_(cs%visc_rem_v(isd:ied,jsdb:jedb,nz)) ; cs%visc_rem_v(:,:,:) = 0.0
1016  alloc_(cs%eta_PF(isd:ied,jsd:jed)) ; cs%eta_PF(:,:) = 0.0
1017  alloc_(cs%pbce(isd:ied,jsd:jed,nz)) ; cs%pbce(:,:,:) = 0.0
1018 
1019  alloc_(cs%u_accel_bt(isdb:iedb,jsd:jed,nz)) ; cs%u_accel_bt(:,:,:) = 0.0
1020  alloc_(cs%v_accel_bt(isd:ied,jsdb:jedb,nz)) ; cs%v_accel_bt(:,:,:) = 0.0
1021 
1022  mis%diffu => cs%diffu
1023  mis%diffv => cs%diffv
1024  mis%PFu => cs%PFu
1025  mis%PFv => cs%PFv
1026  mis%CAu => cs%CAu
1027  mis%CAv => cs%CAv
1028  mis%pbce => cs%pbce
1029  mis%u_accel_bt => cs%u_accel_bt
1030  mis%v_accel_bt => cs%v_accel_bt
1031  mis%u_av => cs%u_av
1032  mis%v_av => cs%v_av
1033 
1034  cs%ADp => accel_diag
1035  cs%CDp => cont_diag
1036  accel_diag%diffu => cs%diffu
1037  accel_diag%diffv => cs%diffv
1038  accel_diag%PFu => cs%PFu
1039  accel_diag%PFv => cs%PFv
1040  accel_diag%CAu => cs%CAu
1041  accel_diag%CAv => cs%CAv
1042 
1043 ! Accel_diag%pbce => CS%pbce
1044 ! Accel_diag%u_accel_bt => CS%u_accel_bt ; Accel_diag%v_accel_bt => CS%v_accel_bt
1045 ! Accel_diag%u_av => CS%u_av ; Accel_diag%v_av => CS%v_av
1046 
1047  call continuity_init(time, g, gv, param_file, diag, cs%continuity_CSp)
1048  call coriolisadv_init(time, g, param_file, diag, cs%ADp, cs%CoriolisAdv_CSp)
1049  if (use_tides) call tidal_forcing_init(time, g, param_file, cs%tides_CSp)
1050  call pressureforce_init(time, g, gv, param_file, diag, cs%PressureForce_CSp, &
1051  cs%tides_CSp)
1052  call hor_visc_init(time, g, param_file, diag, cs%hor_visc_CSp)
1053  call vertvisc_init(mis, time, g, gv, param_file, diag, cs%ADp, dirs, &
1054  ntrunc, cs%vertvisc_CSp)
1055  if (.not.associated(setvisc_csp)) call mom_error(fatal, &
1056  "initialize_dyn_split_RK2 called with setVisc_CSp unassociated.")
1057  cs%set_visc_CSp => setvisc_csp
1058  call updatecfltruncationvalue(time, cs%vertvisc_CSp, activate= &
1059  ((dirs%input_filename(1:1) == 'n') .and. &
1060  (len_trim(dirs%input_filename) == 1)) )
1061 
1062  if (associated(ale_csp)) cs%ALE_CSp => ale_csp
1063  if (associated(obc)) cs%OBC => obc
1064  if (associated(update_obc_csp)) cs%update_OBC_CSp => update_obc_csp
1065 
1066  if (.not. query_initialized(cs%eta,"sfc",restart_cs)) then
1067  ! Estimate eta based on the layer thicknesses - h. With the Boussinesq
1068  ! approximation, eta is the free surface height anomaly, while without it
1069  ! eta is the mass of ocean per unit area. eta always has the same
1070  ! dimensions as h, either m or kg m-3.
1071  ! CS%eta(:,:) = 0.0 already from initialization.
1072  if (gv%Boussinesq) then
1073  do j=js,je ; do i=is,ie ; cs%eta(i,j) = -g%bathyT(i,j) * gv%m_to_H ; enddo ; enddo
1074  endif
1075  do k=1,nz ; do j=js,je ; do i=is,ie
1076  cs%eta(i,j) = cs%eta(i,j) + h(i,j,k)
1077  enddo ; enddo ; enddo
1078  endif
1079  ! Copy eta into an output array.
1080  do j=js,je ; do i=is,ie ; eta(i,j) = cs%eta(i,j) ; enddo ; enddo
1081 
1082  call barotropic_init(u, v, h, cs%eta, time, g, gv, param_file, diag, &
1083  cs%barotropic_CSp, restart_cs, cs%BT_cont, cs%tides_CSp)
1084 
1085  if (.not. query_initialized(cs%diffu,"diffu",restart_cs) .or. &
1086  .not. query_initialized(cs%diffv,"diffv",restart_cs)) &
1087  call horizontal_viscosity(u, v, h, cs%diffu, cs%diffv, meke, varmix, &
1088  g, gv, cs%hor_visc_CSp, obc=cs%OBC)
1089  if (.not. query_initialized(cs%u_av,"u2", restart_cs) .or. &
1090  .not. query_initialized(cs%u_av,"v2", restart_cs)) then
1091  cs%u_av(:,:,:) = u(:,:,:)
1092  cs%v_av(:,:,:) = v(:,:,:)
1093  endif
1094 
1095  ! This call is just here to initialize uh and vh.
1096  if (.not. query_initialized(uh,"uh",restart_cs) .or. &
1097  .not. query_initialized(vh,"vh",restart_cs)) then
1098  h_tmp(:,:,:) = h(:,:,:)
1099  call continuity(u, v, h, h_tmp, uh, vh, dt, g, gv, cs%continuity_CSp, obc=cs%OBC)
1100  call cpu_clock_begin(id_clock_pass_init)
1101  call create_group_pass(pass_h_tmp, h_tmp, g%Domain)
1102  call do_group_pass(pass_h_tmp, g%Domain)
1103  call cpu_clock_end(id_clock_pass_init)
1104  cs%h_av(:,:,:) = 0.5*(h(:,:,:) + h_tmp(:,:,:))
1105  else
1106  if (.not. query_initialized(cs%h_av,"h2",restart_cs)) &
1107  cs%h_av(:,:,:) = h(:,:,:)
1108  endif
1109 
1110  call cpu_clock_begin(id_clock_pass_init)
1111  call create_group_pass(pass_av_h_uvh, cs%u_av, cs%v_av, g%Domain, halo=2)
1112  call create_group_pass(pass_av_h_uvh, cs%h_av, g%Domain, halo=2)
1113  call create_group_pass(pass_av_h_uvh, uh, vh, g%Domain, halo=2)
1114  call do_group_pass(pass_av_h_uvh, g%Domain)
1115  call cpu_clock_end(id_clock_pass_init)
1116 
1117  flux_units = get_flux_units(gv)
1118  cs%id_uh = register_diag_field('ocean_model', 'uh', diag%axesCuL, time, &
1119  'Zonal Thickness Flux', flux_units, y_cell_method='sum', v_extensive=.true.)
1120  cs%id_vh = register_diag_field('ocean_model', 'vh', diag%axesCvL, time, &
1121  'Meridional Thickness Flux', flux_units, x_cell_method='sum', v_extensive=.true.)
1122 
1123  cs%id_CAu = register_diag_field('ocean_model', 'CAu', diag%axesCuL, time, &
1124  'Zonal Coriolis and Advective Acceleration', 'meter second-2')
1125  cs%id_CAv = register_diag_field('ocean_model', 'CAv', diag%axesCvL, time, &
1126  'Meridional Coriolis and Advective Acceleration', 'meter second-2')
1127  cs%id_PFu = register_diag_field('ocean_model', 'PFu', diag%axesCuL, time, &
1128  'Zonal Pressure Force Acceleration', 'meter second-2')
1129  cs%id_PFv = register_diag_field('ocean_model', 'PFv', diag%axesCvL, time, &
1130  'Meridional Pressure Force Acceleration', 'meter second-2')
1131 
1132  cs%id_uav = register_diag_field('ocean_model', 'uav', diag%axesCuL, time, &
1133  'Barotropic-step Averaged Zonal Velocity', 'meter second-1')
1134  cs%id_vav = register_diag_field('ocean_model', 'vav', diag%axesCvL, time, &
1135  'Barotropic-step Averaged Meridional Velocity', 'meter second-1')
1136 
1137  cs%id_u_BT_accel = register_diag_field('ocean_model', 'u_BT_accel', diag%axesCuL, time, &
1138  'Barotropic Anomaly Zonal Acceleration', 'meter second-1')
1139  cs%id_v_BT_accel = register_diag_field('ocean_model', 'v_BT_accel', diag%axesCvL, time, &
1140  'Barotropic Anomaly Meridional Acceleration', 'meter second-1')
1141 
1142  id_clock_cor = cpu_clock_id('(Ocean Coriolis & mom advection)', grain=clock_module)
1143  id_clock_continuity = cpu_clock_id('(Ocean continuity equation)', grain=clock_module)
1144  id_clock_pres = cpu_clock_id('(Ocean pressure force)', grain=clock_module)
1145  id_clock_vertvisc = cpu_clock_id('(Ocean vertical viscosity)', grain=clock_module)
1146  id_clock_horvisc = cpu_clock_id('(Ocean horizontal viscosity)', grain=clock_module)
1147  id_clock_mom_update = cpu_clock_id('(Ocean momentum increments)', grain=clock_module)
1148  id_clock_pass = cpu_clock_id('(Ocean message passing)', grain=clock_module)
1149  id_clock_pass_init = cpu_clock_id('(Ocean init message passing)', grain=clock_routine)
1150  id_clock_btcalc = cpu_clock_id('(Ocean barotropic mode calc)', grain=clock_module)
1151  id_clock_btstep = cpu_clock_id('(Ocean barotropic mode stepping)', grain=clock_module)
1152  id_clock_btforce = cpu_clock_id('(Ocean barotropic forcing calc)', grain=clock_module)
1153 

◆ register_restarts_dyn_split_rk2()

subroutine, public mom_dynamics_split_rk2::register_restarts_dyn_split_rk2 ( type(hor_index_type), intent(in)  HI,
type(verticalgrid_type), intent(in)  GV,
type(param_file_type), intent(in)  param_file,
type(mom_dyn_split_rk2_cs), pointer  CS,
type(mom_restart_cs), pointer  restart_CS,
real, dimension(szib_(hi),szj_(hi),szk_(gv)), intent(inout), target  uh,
real, dimension(szi_(hi),szjb_(hi),szk_(gv)), intent(inout), target  vh 
)

This subroutine sets up any auxiliary restart variables that are specific to the unsplit time stepping scheme. All variables registered here should have the ability to be recreated if they are not present in a restart file.

Parameters
[in]hiHorizontal index structure
[in]gvocean vertical grid structure
[in]param_fileparameter file
csmodule control structure
restart_csrestart control structure
[in,out]uhzonal volume/mass transport (m3/s or kg/s)
[in,out]vhmerid volume/mass transport (m3/s or kg/s)

Definition at line 853 of file MOM_dynamics_split_RK2.F90.

853  type(hor_index_type), intent(in) :: hi !< Horizontal index structure
854  type(verticalgrid_type), intent(in) :: gv !< ocean vertical grid structure
855  type(param_file_type), intent(in) :: param_file !< parameter file
856  type(mom_dyn_split_rk2_cs), pointer :: cs !< module control structure
857  type(mom_restart_cs), pointer :: restart_cs !< restart control structure
858  real, dimension(SZIB_(HI),SZJ_(HI),SZK_(GV)), target, intent(inout) :: uh !< zonal volume/mass transport (m3/s or kg/s)
859  real, dimension(SZI_(HI),SZJB_(HI),SZK_(GV)), target, intent(inout) :: vh !< merid volume/mass transport (m3/s or kg/s)
860 
861  type(vardesc) :: vd
862  character(len=40) :: mdl = "MOM_dynamics_split_RK2" ! This module's name.
863  character(len=48) :: thickness_units, flux_units
864 
865  integer :: isd, ied, jsd, jed, nz, isdb, iedb, jsdb, jedb
866  isd = hi%isd ; ied = hi%ied ; jsd = hi%jsd ; jed = hi%jed ; nz = gv%ke
867  isdb = hi%IsdB ; iedb = hi%IedB ; jsdb = hi%JsdB ; jedb = hi%JedB
868 
869  ! This is where a control structure specific to this module would be allocated.
870  if (associated(cs)) then
871  call mom_error(warning, "register_restarts_dyn_split_RK2 called with an associated "// &
872  "control structure.")
873  return
874  endif
875  allocate(cs)
876 
877  alloc_(cs%diffu(isdb:iedb,jsd:jed,nz)) ; cs%diffu(:,:,:) = 0.0
878  alloc_(cs%diffv(isd:ied,jsdb:jedb,nz)) ; cs%diffv(:,:,:) = 0.0
879  alloc_(cs%CAu(isdb:iedb,jsd:jed,nz)) ; cs%CAu(:,:,:) = 0.0
880  alloc_(cs%CAv(isd:ied,jsdb:jedb,nz)) ; cs%CAv(:,:,:) = 0.0
881  alloc_(cs%PFu(isdb:iedb,jsd:jed,nz)) ; cs%PFu(:,:,:) = 0.0
882  alloc_(cs%PFv(isd:ied,jsdb:jedb,nz)) ; cs%PFv(:,:,:) = 0.0
883 
884  alloc_(cs%eta(isd:ied,jsd:jed)) ; cs%eta(:,:) = 0.0
885  alloc_(cs%u_av(isdb:iedb,jsd:jed,nz)) ; cs%u_av(:,:,:) = 0.0
886  alloc_(cs%v_av(isd:ied,jsdb:jedb,nz)) ; cs%v_av(:,:,:) = 0.0
887  alloc_(cs%h_av(isd:ied,jsd:jed,nz)) ; cs%h_av(:,:,:) = gv%Angstrom
888 
889  thickness_units = get_thickness_units(gv)
890  flux_units = get_flux_units(gv)
891 
892  vd = var_desc("sfc",thickness_units,"Free surface Height",'h','1')
893  call register_restart_field(cs%eta, vd, .false., restart_cs)
894 
895  vd = var_desc("u2","meter second-1","Auxiliary Zonal velocity",'u','L')
896  call register_restart_field(cs%u_av, vd, .false., restart_cs)
897 
898  vd = var_desc("v2","meter second-1","Auxiliary Meridional velocity",'v','L')
899  call register_restart_field(cs%v_av, vd, .false., restart_cs)
900 
901  vd = var_desc("h2",thickness_units,"Auxiliary Layer Thickness",'h','L')
902  call register_restart_field(cs%h_av, vd, .false., restart_cs)
903 
904  vd = var_desc("uh",flux_units,"Zonal thickness flux",'u','L')
905  call register_restart_field(uh, vd, .false., restart_cs)
906 
907  vd = var_desc("vh",flux_units,"Meridional thickness flux",'v','L')
908  call register_restart_field(vh, vd, .false., restart_cs)
909 
910  vd = var_desc("diffu","meter second-2","Zonal horizontal viscous acceleration",'u','L')
911  call register_restart_field(cs%diffu, vd, .false., restart_cs)
912 
913  vd = var_desc("diffv","meter second-2","Meridional horizontal viscous acceleration",'v','L')
914  call register_restart_field(cs%diffv, vd, .false., restart_cs)
915 
916  call register_barotropic_restarts(hi, gv, param_file, cs%barotropic_CSp, &
917  restart_cs)
918 

◆ step_mom_dyn_split_rk2()

subroutine, public mom_dynamics_split_rk2::step_mom_dyn_split_rk2 ( real, dimension(szib_(g),szj_(g),szk_(g)), intent(inout), target  u,
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(inout), target  v,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(inout)  h,
type(thermo_var_ptrs), intent(in)  tv,
type(vertvisc_type), intent(inout)  visc,
type(time_type), intent(in)  Time_local,
real, intent(in)  dt,
type(forcing), intent(in)  fluxes,
real, dimension(:,:), pointer  p_surf_begin,
real, dimension(:,:), pointer  p_surf_end,
real, intent(in)  dt_since_flux,
real, intent(in)  dt_therm,
real, dimension(szib_(g),szj_(g),szk_(g)), intent(inout), target  uh,
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(inout), target  vh,
real, dimension(szib_(g),szj_(g),szk_(g)), intent(inout)  uhtr,
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(inout)  vhtr,
real, dimension(szi_(g),szj_(g)), intent(out)  eta_av,
type(ocean_grid_type), intent(inout)  G,
type(verticalgrid_type), intent(in)  GV,
type(mom_dyn_split_rk2_cs), pointer  CS,
logical, intent(in)  calc_dtbt,
type(varmix_cs), pointer  VarMix,
type(meke_type), pointer  MEKE 
)

RK2 splitting for time stepping MOM adiabatic dynamics.

Parameters
[in,out]gocean grid structure
[in]gvocean vertical grid structure
[in,out]uzonal velocity (m/s)
[in,out]vmerid velocity (m/s)
[in,out]hlayer thickness (m or kg/m2)
[in]tvthermodynamic type
[in,out]viscvertical visc, bottom drag, and related
[in]time_localmodel time at end of time step
[in]dttime step (sec)
[in]fluxesforcing fields
p_surf_beginsurf pressure at start of this dynamic time step (Pa)
p_surf_endsurf pressure at end of this dynamic time step (Pa)
[in]dt_since_fluxelapsed time since fluxes were applied (sec)
[in]dt_thermthermodynamic time step (sec)
[in,out]uhzonal volume/mass transport (m3/s or kg/s)
[in,out]vhmerid volume/mass transport (m3/s or kg/s)
[in,out]uhtraccumulatated zonal volume/mass transport since last tracer advection (m3 or kg)
[in,out]vhtraccumulatated merid volume/mass transport since last tracer advection (m3 or kg)
[out]eta_avfree surface height or column mass time averaged over time step (m or kg/m2)
csmodule control structure
[in]calc_dtbtif true, recalculate barotropic time step
varmixspecify the spatially varying viscosities
mekerelated to mesoscale eddy kinetic energy param

Definition at line 205 of file MOM_dynamics_split_RK2.F90.

References mom_error_handler::calltree_enter(), mom_error_handler::calltree_leave(), mom_error_handler::calltree_waypoint(), mom_domains::complete_group_pass(), mom_continuity::continuity_stencil(), mom_coriolisadv::coradcalc(), mom_diag_mediator::diag_update_remap_grids(), mom_hor_visc::horizontal_viscosity(), id_clock_btcalc, id_clock_btforce, id_clock_btstep, id_clock_continuity, id_clock_cor, id_clock_horvisc, id_clock_mom_update, id_clock_pass, id_clock_pres, id_clock_vertvisc, mom_checksum_packages::mom_accel_chksum(), mom_open_boundary::open_boundary_zero_normal_flow(), mom_pressureforce::pressureforce(), mom_barotropic::set_dtbt(), mom_set_visc::set_viscous_ml(), mom_domains::start_group_pass(), mom_boundary_update::update_obc_data(), and mom_vert_friction::updatecfltruncationvalue().

205  type(ocean_grid_type), intent(inout) :: g !< ocean grid structure
206  type(verticalgrid_type), intent(in) :: gv !< ocean vertical grid structure
207  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target, intent(inout) :: u !< zonal velocity (m/s)
208  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target, intent(inout) :: v !< merid velocity (m/s)
209  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: h !< layer thickness (m or kg/m2)
210  type(thermo_var_ptrs), intent(in) :: tv !< thermodynamic type
211  type(vertvisc_type), intent(inout) :: visc !< vertical visc, bottom drag, and related
212  type(time_type), intent(in) :: time_local !< model time at end of time step
213  real, intent(in) :: dt !< time step (sec)
214  type(forcing), intent(in) :: fluxes !< forcing fields
215  real, dimension(:,:), pointer :: p_surf_begin !< surf pressure at start of this dynamic time step (Pa)
216  real, dimension(:,:), pointer :: p_surf_end !< surf pressure at end of this dynamic time step (Pa)
217  real, intent(in) :: dt_since_flux !< elapsed time since fluxes were applied (sec)
218  real, intent(in) :: dt_therm !< thermodynamic time step (sec)
219  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target, intent(inout) :: uh !< zonal volume/mass transport (m3/s or kg/s)
220  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target, intent(inout) :: vh !< merid volume/mass transport (m3/s or kg/s)
221  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(inout) :: uhtr !< accumulatated zonal volume/mass transport since last tracer advection (m3 or kg)
222  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(inout) :: vhtr !< accumulatated merid volume/mass transport since last tracer advection (m3 or kg)
223  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: eta_av !< free surface height or column mass time averaged over time step (m or kg/m2)
224  type(mom_dyn_split_rk2_cs), pointer :: cs !< module control structure
225  logical, intent(in) :: calc_dtbt !< if true, recalculate barotropic time step
226  type(varmix_cs), pointer :: varmix !< specify the spatially varying viscosities
227  type(meke_type), pointer :: meke !< related to mesoscale eddy kinetic energy param
228 
229  real :: dt_pred ! The time step for the predictor part of the baroclinic time stepping.
230 
231  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)) :: up ! Predicted zonal velocity in m s-1.
232  real, dimension(SZI_(G),SZJB_(G),SZK_(G)) :: vp ! Predicted meridional velocity in m s-1.
233  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: hp ! Predicted thickness in m or kg m-2 (H).
234 
235  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)) :: u_bc_accel
236  real, dimension(SZI_(G),SZJB_(G),SZK_(G)) :: v_bc_accel
237  ! u_bc_accel and v_bc_accel are the summed baroclinic accelerations of each
238  ! layer calculated by the non-barotropic part of the model, both in m s-2.
239 
240  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target :: uh_in
241  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target :: vh_in
242  ! uh_in and vh_in are the zonal or meridional mass transports that would be
243  ! obtained using the initial velocities, both in m3 s-1 or kg s-1.
244 
245  real, dimension(SZIB_(G),SZJ_(G)) :: uhbt_out
246  real, dimension(SZI_(G),SZJB_(G)) :: vhbt_out
247  ! uhbt_out and vhbt_out are the vertically summed transports from the
248  ! barotropic solver based on its final velocities, both in m3 s-1 or kg s-1.
249 
250  real, dimension(SZI_(G),SZJ_(G)) :: eta_pred
251  ! eta_pred is the predictor value of the free surface height or column mass,
252  ! in m or kg m-2.
253 
254  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target :: u_adj
255  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target :: v_adj
256  ! u_adj and v_adj are the zonal or meridional velocities after u and v
257  ! have been barotropically adjusted so the resulting transports match
258  ! uhbt_out and vhbt_out, both in m s-1.
259 
260  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)) :: u_old_rad_obc
261  real, dimension(SZI_(G),SZJB_(G),SZK_(G)) :: v_old_rad_obc
262  ! u_old_rad_OBC and v_old_rad_OBC are the starting velocities, which are
263  ! saved for use in the Flather open boundary condition code, both in m s-1.
264 
265  real :: pa_to_eta ! A factor that converts pressures to the units of eta.
266  real, pointer, dimension(:,:) :: &
267  p_surf => null(), eta_pf_start => null(), &
268  taux_bot => null(), tauy_bot => null(), &
269  eta => null()
270 
271  real, pointer, dimension(:,:,:) :: &
272  uh_ptr => null(), u_ptr => null(), vh_ptr => null(), v_ptr => null(), &
273  u_init => null(), v_init => null(), & ! Pointers to u and v or u_adj and v_adj.
274  u_av, & ! The zonal velocity time-averaged over a time step, in m s-1.
275  v_av, & ! The meridional velocity time-averaged over a time step, in m s-1.
276  h_av ! The layer thickness time-averaged over a time step, in m or
277  ! kg m-2.
278  real :: idt
279  logical :: dyn_p_surf
280  logical :: bt_cont_bt_thick ! If true, use the BT_cont_type to estimate the
281  ! relative weightings of the layers in calculating
282  ! the barotropic accelerations.
283  !---For group halo pass
284  logical :: showcalltree, sym
285 
286  integer :: i, j, k, is, ie, js, je, isq, ieq, jsq, jeq, nz
287  integer :: cont_stencil
288  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
289  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
290  u_av => cs%u_av ; v_av => cs%v_av ; h_av => cs%h_av ; eta => cs%eta
291  idt = 1.0 / dt
292 
293  sym=.false.;if (g%Domain%symmetric) sym=.true. ! switch to include symmetric domain in checksums
294 
295  showcalltree = calltree_showquery()
296  if (showcalltree) call calltree_enter("step_MOM_dyn_split_RK2(), MOM_dynamics_split_RK2.F90")
297 
298  !$OMP parallel do default(shared)
299  do k = 1, nz
300  do j=g%jsd,g%jed ; do i=g%isdB,g%iedB ; up(i,j,k) = 0.0 ; enddo ; enddo
301  do j=g%jsdB,g%jedB ; do i=g%isd,g%ied ; vp(i,j,k) = 0.0 ; enddo ; enddo
302  do j=g%jsd,g%jed ; do i=g%isd,g%ied ; hp(i,j,k) = h(i,j,k) ; enddo ; enddo
303  enddo
304 
305  ! Update CFL truncation value as function of time
306  call updatecfltruncationvalue(time_local, cs%vertvisc_CSp)
307 
308  if (cs%debug) then
309  call mom_state_chksum("Start predictor ", u, v, h, uh, vh, g, gv, symmetric=sym)
310  call check_redundant("Start predictor u ", u, v, g)
311  call check_redundant("Start predictor uh ", uh, vh, g)
312  endif
313 
314  dyn_p_surf = associated(p_surf_begin) .and. associated(p_surf_end)
315  if (dyn_p_surf) then
316  p_surf => p_surf_end
317  call safe_alloc_ptr(eta_pf_start,g%isd,g%ied,g%jsd,g%jed)
318  eta_pf_start(:,:) = 0.0
319  else
320  p_surf => fluxes%p_surf
321  endif
322 
323  if (associated(cs%OBC)) then
324  do k=1,nz ; do j=js-1,je+1 ; do i=is-2,ie+1
325  u_old_rad_obc(i,j,k) = u_av(i,j,k)
326  enddo ; enddo ; enddo
327  do k=1,nz ; do j=js-2,je+1 ; do i=is-1,ie+1
328  v_old_rad_obc(i,j,k) = v_av(i,j,k)
329  enddo ; enddo ; enddo
330  endif
331 
332  bt_cont_bt_thick = .false.
333  if (associated(cs%BT_cont)) bt_cont_bt_thick = &
334  (associated(cs%BT_cont%h_u) .and. associated(cs%BT_cont%h_v))
335 
336  if (cs%split_bottom_stress) then
337  taux_bot => cs%taux_bot ; tauy_bot => cs%tauy_bot
338  endif
339 
340  !--- begin set up for group halo pass
341 
342  call cpu_clock_begin(id_clock_pass)
343  cont_stencil = continuity_stencil(cs%continuity_CSp)
344  !### Apart from circle_OBCs halo for eta could be 1, but halo>=3 is required
345  !### to match circle_OBCs solutions. Why?
346  call create_group_pass(cs%pass_eta, eta, g%Domain) !### , halo=1)
347  call create_group_pass(cs%pass_visc_rem, cs%visc_rem_u, cs%visc_rem_v, g%Domain, &
348  to_all+scalar_pair, cgrid_ne, halo=max(1,cont_stencil))
349  call create_group_pass(cs%pass_uvp, up, vp, g%Domain, halo=max(1,cont_stencil))
350  call create_group_pass(cs%pass_hp_uv, hp, g%Domain, halo=2)
351  call create_group_pass(cs%pass_hp_uv, u_av, v_av, g%Domain, halo=2)
352  call create_group_pass(cs%pass_hp_uv, uh(:,:,:), vh(:,:,:), g%Domain, halo=2)
353 
354  call create_group_pass(cs%pass_uv, u, v, g%Domain, halo=max(2,cont_stencil))
355  call create_group_pass(cs%pass_h, h, g%Domain, halo=max(2,cont_stencil))
356  call create_group_pass(cs%pass_av_uvh, u_av, v_av, g%Domain, halo=2)
357  call create_group_pass(cs%pass_av_uvh, uh(:,:,:), vh(:,:,:), g%Domain, halo=2)
358  call cpu_clock_end(id_clock_pass)
359  !--- end set up for group halo pass
360 
361 
362 ! PFu = d/dx M(h,T,S)
363 ! pbce = dM/deta
364  if (cs%begw == 0.0) call enable_averaging(dt, time_local, cs%diag)
365  call cpu_clock_begin(id_clock_pres)
366  call pressureforce(h, tv, cs%PFu, cs%PFv, g, gv, cs%PressureForce_CSp, &
367  cs%ALE_CSp, p_surf, cs%pbce, cs%eta_PF)
368  if (dyn_p_surf) then
369  pa_to_eta = 1.0 / gv%H_to_Pa
370  !$OMP parallel do default(shared)
371  do j=jsq,jeq+1 ; do i=isq,ieq+1
372  eta_pf_start(i,j) = cs%eta_PF(i,j) - pa_to_eta * &
373  (p_surf_begin(i,j) - p_surf_end(i,j))
374  enddo ; enddo
375  endif
376  call cpu_clock_end(id_clock_pres)
377  call disable_averaging(cs%diag)
378  if (showcalltree) call calltree_waypoint("done with PressureForce (step_MOM_dyn_split_RK2)")
379 
380  if (associated(cs%OBC)) then; if (cs%OBC%update_OBC) then
381  call update_obc_data(cs%OBC, g, gv, tv, h, cs%update_OBC_CSp, time_local)
382  endif; endif
383 
384  if (g%nonblocking_updates) then
385  call cpu_clock_begin(id_clock_pass)
386  call start_group_pass(cs%pass_eta, g%Domain)
387  call cpu_clock_end(id_clock_pass)
388  endif
389 
390 ! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av
391  call cpu_clock_begin(id_clock_cor)
392  call coradcalc(u_av, v_av, h_av, uh, vh, cs%CAu, cs%CAv, cs%OBC, cs%ADp, &
393  g, gv, cs%CoriolisAdv_CSp)
394  call cpu_clock_end(id_clock_cor)
395  if (showcalltree) call calltree_waypoint("done with CorAdCalc (step_MOM_dyn_split_RK2)")
396 
397 ! u_bc_accel = CAu + PFu + diffu(u[n-1])
398  call cpu_clock_begin(id_clock_btforce)
399  !$OMP parallel do default(shared)
400  do k=1,nz
401  do j=js,je ; do i=isq,ieq
402  u_bc_accel(i,j,k) = (cs%Cau(i,j,k) + cs%PFu(i,j,k)) + cs%diffu(i,j,k)
403  enddo ; enddo
404  do j=jsq,jeq ; do i=is,ie
405  v_bc_accel(i,j,k) = (cs%Cav(i,j,k) + cs%PFv(i,j,k)) + cs%diffv(i,j,k)
406  enddo ; enddo
407  enddo
408  if (associated(cs%OBC)) then
409  call open_boundary_zero_normal_flow(cs%OBC, g, u_bc_accel, v_bc_accel)
410  endif
411  call cpu_clock_end(id_clock_btforce)
412 
413  if (cs%debug) then
414  call mom_accel_chksum("pre-btstep accel", cs%CAu, cs%CAv, cs%PFu, cs%PFv, &
415  cs%diffu, cs%diffv, g, gv, cs%pbce, u_bc_accel, v_bc_accel, &
416  symmetric=sym)
417  call check_redundant("pre-btstep CS%Ca ", cs%Cau, cs%Cav, g)
418  call check_redundant("pre-btstep CS%PF ", cs%PFu, cs%PFv, g)
419  call check_redundant("pre-btstep CS%diff ", cs%diffu, cs%diffv, g)
420  call check_redundant("pre-btstep u_bc_accel ", u_bc_accel, v_bc_accel, g)
421  endif
422 
423  call cpu_clock_begin(id_clock_vertvisc)
424  !$OMP parallel do default(shared)
425  do k=1,nz
426  do j=js,je ; do i=isq,ieq
427  up(i,j,k) = g%mask2dCu(i,j) * (u(i,j,k) + dt * u_bc_accel(i,j,k))
428  enddo ; enddo
429  do j=jsq,jeq ; do i=is,ie
430  vp(i,j,k) = g%mask2dCv(i,j) * (v(i,j,k) + dt * v_bc_accel(i,j,k))
431  enddo ; enddo
432  enddo
433 
434  call enable_averaging(dt, time_local, cs%diag)
435  call set_viscous_ml(u, v, h, tv, fluxes, visc, dt, g, gv, &
436  cs%set_visc_CSp)
437  call disable_averaging(cs%diag)
438 
439  if (cs%debug) then
440  call uvchksum("before vertvisc: up", up, vp, g%HI, haloshift=0, symmetric=sym)
441  endif
442  call vertvisc_coef(up, vp, h, fluxes, visc, dt, g, gv, cs%vertvisc_CSp, cs%OBC)
443  call vertvisc_remnant(visc, cs%visc_rem_u, cs%visc_rem_v, dt, g, gv, cs%vertvisc_CSp)
444  call cpu_clock_end(id_clock_vertvisc)
445  if (showcalltree) call calltree_waypoint("done with vertvisc_coef (step_MOM_dyn_split_RK2)")
446 
447 
448  call cpu_clock_begin(id_clock_pass)
449  if (g%nonblocking_updates) then
450  call complete_group_pass(cs%pass_eta, g%Domain)
451  call start_group_pass(cs%pass_visc_rem, g%Domain)
452  else
453  call do_group_pass(cs%pass_eta, g%Domain)
454  call do_group_pass(cs%pass_visc_rem, g%Domain)
455  endif
456  call cpu_clock_end(id_clock_pass)
457 
458  call cpu_clock_begin(id_clock_btcalc)
459  ! Calculate the relative layer weights for determining barotropic quantities.
460  if (.not.bt_cont_bt_thick) &
461  call btcalc(h, g, gv, cs%barotropic_CSp, obc=cs%OBC)
462  call bt_mass_source(h, eta, fluxes, .true., dt_therm, dt_since_flux, &
463  g, gv, cs%barotropic_CSp)
464  call cpu_clock_end(id_clock_btcalc)
465 
466  if (g%nonblocking_updates) then
467  call cpu_clock_begin(id_clock_pass)
468  call complete_group_pass(cs%pass_visc_rem, g%Domain)
469  call cpu_clock_end(id_clock_pass)
470  endif
471 
472 ! u_accel_bt = layer accelerations due to barotropic solver
473  if (associated(cs%BT_cont) .or. cs%BT_use_layer_fluxes) then
474  call cpu_clock_begin(id_clock_continuity)
475  call continuity(u, v, h, hp, uh_in, vh_in, dt, g, gv, &
476  cs%continuity_CSp, obc=cs%OBC, visc_rem_u=cs%visc_rem_u, &
477  visc_rem_v=cs%visc_rem_v, bt_cont=cs%BT_cont)
478  call cpu_clock_end(id_clock_continuity)
479  if (bt_cont_bt_thick) then
480  call btcalc(h, g, gv, cs%barotropic_CSp, cs%BT_cont%h_u, cs%BT_cont%h_v, &
481  obc=cs%OBC)
482  endif
483  if (showcalltree) call calltree_waypoint("done with continuity[BT_cont] (step_MOM_dyn_split_RK2)")
484  endif
485 
486  if (cs%BT_use_layer_fluxes) then
487  uh_ptr => uh_in; vh_ptr => vh_in; u_ptr => u; v_ptr => v
488  endif
489 
490  u_init => u ; v_init => v
491  call cpu_clock_begin(id_clock_btstep)
492  if (calc_dtbt) call set_dtbt(g, gv, cs%barotropic_CSp, eta, cs%pbce)
493  if (showcalltree) call calltree_enter("btstep(), MOM_barotropic.F90")
494  ! This is the predictor step call to btstep.
495  call btstep(u, v, eta, dt, u_bc_accel, v_bc_accel, &
496  fluxes, cs%pbce, cs%eta_PF, u_av, v_av, cs%u_accel_bt, &
497  cs%v_accel_bt, eta_pred, cs%uhbt, cs%vhbt, g, gv, cs%barotropic_CSp,&
498  cs%visc_rem_u, cs%visc_rem_v, obc=cs%OBC, &
499  bt_cont = cs%BT_cont, eta_pf_start=eta_pf_start, &
500  taux_bot=taux_bot, tauy_bot=tauy_bot, &
501  uh0=uh_ptr, vh0=vh_ptr, u_uh0=u_ptr, v_vh0=v_ptr)
502  if (showcalltree) call calltree_leave("btstep()")
503  call cpu_clock_end(id_clock_btstep)
504 
505 ! up = u + dt_pred*( u_bc_accel + u_accel_bt )
506  dt_pred = dt * cs%be
507  call cpu_clock_begin(id_clock_mom_update)
508 
509  !$OMP parallel do default(shared)
510  do k=1,nz
511  do j=jsq,jeq ; do i=is,ie
512  vp(i,j,k) = g%mask2dCv(i,j) * (v_init(i,j,k) + dt_pred * &
513  (v_bc_accel(i,j,k) + cs%v_accel_bt(i,j,k)))
514  enddo ; enddo
515  do j=js,je ; do i=isq,ieq
516  up(i,j,k) = g%mask2dCu(i,j) * (u_init(i,j,k) + dt_pred * &
517  (u_bc_accel(i,j,k) + cs%u_accel_bt(i,j,k)))
518  enddo ; enddo
519  enddo
520  call cpu_clock_end(id_clock_mom_update)
521 
522  if (cs%debug) then
523  call uvchksum("Predictor 1 [uv]", up, vp, g%HI, haloshift=0, symmetric=sym)
524  call hchksum(h, "Predictor 1 h", g%HI, haloshift=1, scale=gv%H_to_m)
525  call uvchksum("Predictor 1 [uv]h", uh, vh, g%HI,haloshift=2, &
526  symmetric=sym, scale=gv%H_to_m)
527 ! call MOM_state_chksum("Predictor 1", up, vp, h, uh, vh, G, GV, haloshift=1)
528  call mom_accel_chksum("Predictor accel", cs%CAu, cs%CAv, cs%PFu, cs%PFv, &
529  cs%diffu, cs%diffv, g, gv, cs%pbce, cs%u_accel_bt, cs%v_accel_bt, symmetric=sym)
530  call mom_state_chksum("Predictor 1 init", u_init, v_init, h, uh, vh, g, gv, haloshift=2, &
531  symmetric=sym)
532  call check_redundant("Predictor 1 up", up, vp, g)
533  call check_redundant("Predictor 1 uh", uh, vh, g)
534  endif
535 
536 ! up <- up + dt_pred d/dz visc d/dz up
537 ! u_av <- u_av + dt_pred d/dz visc d/dz u_av
538  call cpu_clock_begin(id_clock_vertvisc)
539  if (cs%debug) then
540  call uvchksum("0 before vertvisc: [uv]p", up, vp, g%HI,haloshift=0, symmetric=sym)
541  endif
542  call vertvisc_coef(up, vp, h, fluxes, visc, dt_pred, g, gv, cs%vertvisc_CSp, &
543  cs%OBC)
544  call vertvisc(up, vp, h, fluxes, visc, dt_pred, cs%OBC, cs%ADp, cs%CDp, g, &
545  gv, cs%vertvisc_CSp, cs%taux_bot, cs%tauy_bot)
546  if (showcalltree) call calltree_waypoint("done with vertvisc (step_MOM_dyn_split_RK2)")
547  if (g%nonblocking_updates) then
548  call cpu_clock_end(id_clock_vertvisc) ; call cpu_clock_begin(id_clock_pass)
549  call start_group_pass(cs%pass_uvp, g%Domain)
550  call cpu_clock_end(id_clock_pass) ; call cpu_clock_begin(id_clock_vertvisc)
551  endif
552  call vertvisc_remnant(visc, cs%visc_rem_u, cs%visc_rem_v, dt_pred, g, gv, cs%vertvisc_CSp)
553  call cpu_clock_end(id_clock_vertvisc)
554 
555  call cpu_clock_begin(id_clock_pass)
556  call do_group_pass(cs%pass_visc_rem, g%Domain)
557  if (g%nonblocking_updates) then
558  call complete_group_pass(cs%pass_uvp, g%Domain)
559  else
560  call do_group_pass(cs%pass_uvp, g%Domain)
561  endif
562  call cpu_clock_end(id_clock_pass)
563 
564  ! uh = u_av * h
565  ! hp = h + dt * div . uh
566  call cpu_clock_begin(id_clock_continuity)
567  call continuity(up, vp, h, hp, uh, vh, dt, g, gv, cs%continuity_CSp, &
568  cs%uhbt, cs%vhbt, cs%OBC, cs%visc_rem_u, cs%visc_rem_v, &
569  u_av, v_av, bt_cont=cs%BT_cont)
570  call cpu_clock_end(id_clock_continuity)
571  if (showcalltree) call calltree_waypoint("done with continuity (step_MOM_dyn_split_RK2)")
572 
573 
574  if (associated(cs%OBC)) then
575  call cpu_clock_begin(id_clock_pass)
576  ! These should be done with a pass that excludes uh & vh.
577  call do_group_pass(cs%pass_hp_uv, g%Domain)
578  call cpu_clock_end(id_clock_pass)
579 
580  call radiation_open_bdry_conds(cs%OBC, u_av, u_old_rad_obc, v_av, v_old_rad_obc, g, dt_pred)
581  endif
582 
583  call cpu_clock_begin(id_clock_pass)
584  call do_group_pass(cs%pass_hp_uv, g%Domain)
585  if (g%nonblocking_updates) then
586  call start_group_pass(cs%pass_av_uvh, g%Domain)
587  endif
588  call cpu_clock_end(id_clock_pass)
589 
590  ! h_av = (h + hp)/2
591  !$OMP parallel do default(shared)
592  do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2
593  h_av(i,j,k) = 0.5*(h(i,j,k) + hp(i,j,k))
594  enddo ; enddo ; enddo
595 
596  ! The correction phase of the time step starts here.
597  call enable_averaging(dt, time_local, cs%diag)
598 
599  ! Calculate a revised estimate of the free-surface height correction to be
600  ! used in the next call to btstep. This call is at this point so that
601  ! hp can be changed if CS%begw /= 0.
602  ! eta_cor = ... (hidden inside CS%barotropic_CSp)
603  call cpu_clock_begin(id_clock_btcalc)
604  call bt_mass_source(hp, eta_pred, fluxes, .false., dt_therm, &
605  dt_since_flux+dt, g, gv, cs%barotropic_CSp)
606  call cpu_clock_end(id_clock_btcalc)
607 
608  if (cs%begw /= 0.0) then
609  ! hp <- (1-begw)*h_in + begw*hp
610  ! Back up hp to the value it would have had after a time-step of
611  ! begw*dt. hp is not used again until recalculated by continuity.
612  !$OMP parallel do default(shared)
613  do k=1,nz ; do j=js-1,je+1 ; do i=is-1,ie+1
614  hp(i,j,k) = (1.0-cs%begw)*h(i,j,k) + cs%begw*hp(i,j,k)
615  enddo ; enddo ; enddo
616 
617  ! PFu = d/dx M(hp,T,S)
618  ! pbce = dM/deta
619  call cpu_clock_begin(id_clock_pres)
620  call pressureforce(hp, tv, cs%PFu, cs%PFv, g, gv, &
621  cs%PressureForce_CSp, cs%ALE_CSp, &
622  p_surf, cs%pbce, cs%eta_PF)
623  call cpu_clock_end(id_clock_pres)
624  if (showcalltree) call calltree_waypoint("done with PressureForce[hp=(1-b).h+b.h] (step_MOM_dyn_split_RK2)")
625  endif
626 
627  if (g%nonblocking_updates) then
628  call cpu_clock_begin(id_clock_pass)
629  call complete_group_pass(cs%pass_av_uvh, g%Domain)
630  call cpu_clock_end(id_clock_pass)
631  endif
632 
633  if (bt_cont_bt_thick) then
634  call btcalc(h, g, gv, cs%barotropic_CSp, cs%BT_cont%h_u, cs%BT_cont%h_v, &
635  obc=cs%OBC)
636  if (showcalltree) call calltree_waypoint("done with btcalc[BT_cont_BT_thick] (step_MOM_dyn_split_RK2)")
637  endif
638 
639  if (cs%debug) then
640  call mom_state_chksum("Predictor ", up, vp, hp, uh, vh, g, gv, symmetric=sym)
641  call uvchksum("Predictor avg [uv]", u_av, v_av, g%HI, haloshift=1, symmetric=sym)
642  call hchksum(h_av, "Predictor avg h", g%HI, haloshift=0, scale=gv%H_to_m)
643  ! call MOM_state_chksum("Predictor avg ", u_av, v_av, h_av, uh, vh, G, GV)
644  call check_redundant("Predictor up ", up, vp, g)
645  call check_redundant("Predictor uh ", uh, vh, g)
646  endif
647 
648 ! diffu = horizontal viscosity terms (u_av)
649  call cpu_clock_begin(id_clock_horvisc)
650  call horizontal_viscosity(u_av, v_av, h_av, cs%diffu, cs%diffv, &
651  meke, varmix, g, gv, cs%hor_visc_CSp, obc=cs%OBC)
652  call cpu_clock_end(id_clock_horvisc)
653  if (showcalltree) call calltree_waypoint("done with horizontal_viscosity (step_MOM_dyn_split_RK2)")
654 
655 ! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av
656  call cpu_clock_begin(id_clock_cor)
657  call coradcalc(u_av, v_av, h_av, uh, vh, cs%CAu, cs%CAv, cs%OBC, cs%ADp, &
658  g, gv, cs%CoriolisAdv_CSp)
659  call cpu_clock_end(id_clock_cor)
660  if (showcalltree) call calltree_waypoint("done with CorAdCalc (step_MOM_dyn_split_RK2)")
661 
662 ! Calculate the momentum forcing terms for the barotropic equations.
663 
664 ! u_bc_accel = CAu + PFu + diffu(u[n-1])
665  call cpu_clock_begin(id_clock_btforce)
666  !$OMP parallel do default(shared)
667  do k=1,nz
668  do j=js,je ; do i=isq,ieq
669  u_bc_accel(i,j,k) = (cs%Cau(i,j,k) + cs%PFu(i,j,k)) + cs%diffu(i,j,k)
670  enddo ; enddo
671  do j=jsq,jeq ; do i=is,ie
672  v_bc_accel(i,j,k) = (cs%Cav(i,j,k) + cs%PFv(i,j,k)) + cs%diffv(i,j,k)
673  enddo ; enddo
674  enddo
675  if (associated(cs%OBC)) then
676  call open_boundary_zero_normal_flow(cs%OBC, g, u_bc_accel, v_bc_accel)
677  endif
678  call cpu_clock_end(id_clock_btforce)
679 
680  if (cs%debug) then
681  call mom_accel_chksum("corr pre-btstep accel", cs%CAu, cs%CAv, cs%PFu, cs%PFv, &
682  cs%diffu, cs%diffv, g, gv, cs%pbce, u_bc_accel, v_bc_accel, &
683  symmetric=sym)
684  call check_redundant("corr pre-btstep CS%Ca ", cs%Cau, cs%Cav, g)
685  call check_redundant("corr pre-btstep CS%PF ", cs%PFu, cs%PFv, g)
686  call check_redundant("corr pre-btstep CS%diff ", cs%diffu, cs%diffv, g)
687  call check_redundant("corr pre-btstep u_bc_accel ", u_bc_accel, v_bc_accel, g)
688  endif
689 
690  ! u_accel_bt = layer accelerations due to barotropic solver
691  ! pbce = dM/deta
692  call cpu_clock_begin(id_clock_btstep)
693  if (cs%BT_use_layer_fluxes) then
694  uh_ptr => uh ; vh_ptr => vh ; u_ptr => u_av ; v_ptr => v_av
695  endif
696 
697  if (showcalltree) call calltree_enter("btstep(), MOM_barotropic.F90")
698  ! This is the corrector step call to btstep.
699  call btstep(u, v, eta, dt, u_bc_accel, v_bc_accel, &
700  fluxes, cs%pbce, cs%eta_PF, u_av, v_av, cs%u_accel_bt, &
701  cs%v_accel_bt, eta_pred, cs%uhbt, cs%vhbt, g, gv, &
702  cs%barotropic_CSp, cs%visc_rem_u, cs%visc_rem_v, &
703  etaav=eta_av, obc=cs%OBC, &
704  bt_cont = cs%BT_cont, eta_pf_start=eta_pf_start, &
705  taux_bot=taux_bot, tauy_bot=tauy_bot, &
706  uh0=uh_ptr, vh0=vh_ptr, u_uh0=u_ptr, v_vh0=v_ptr)
707  do j=js,je ; do i=is,ie ; eta(i,j) = eta_pred(i,j) ; enddo ; enddo
708  call cpu_clock_end(id_clock_btstep)
709  if (showcalltree) call calltree_leave("btstep()")
710 
711  if (cs%debug) then
712  call check_redundant("u_accel_bt ", cs%u_accel_bt, cs%v_accel_bt, g)
713  endif
714 
715  ! u = u + dt*( u_bc_accel + u_accel_bt )
716  call cpu_clock_begin(id_clock_mom_update)
717  !$OMP parallel do default(shared)
718  do k=1,nz
719  do j=js,je ; do i=isq,ieq
720  u(i,j,k) = g%mask2dCu(i,j) * (u_init(i,j,k) + dt * &
721  (u_bc_accel(i,j,k) + cs%u_accel_bt(i,j,k)))
722  enddo ; enddo
723  do j=jsq,jeq ; do i=is,ie
724  v(i,j,k) = g%mask2dCv(i,j) * (v_init(i,j,k) + dt * &
725  (v_bc_accel(i,j,k) + cs%v_accel_bt(i,j,k)))
726  enddo ; enddo
727  enddo
728  call cpu_clock_end(id_clock_mom_update)
729 
730  if (cs%debug) then
731  call uvchksum("Corrector 1 [uv]", u, v, g%HI,haloshift=0, symmetric=sym)
732  call hchksum(h, "Corrector 1 h", g%HI, haloshift=2, scale=gv%H_to_m)
733  call uvchksum("Corrector 1 [uv]h", uh, vh, g%HI, haloshift=2, &
734  symmetric=sym, scale=gv%H_to_m)
735  ! call MOM_state_chksum("Corrector 1", u, v, h, uh, vh, G, GV, haloshift=1)
736  call mom_accel_chksum("Corrector accel", cs%CAu, cs%CAv, cs%PFu, cs%PFv, &
737  cs%diffu, cs%diffv, g, gv, cs%pbce, cs%u_accel_bt, cs%v_accel_bt, &
738  symmetric=sym)
739  endif
740 
741  ! u <- u + dt d/dz visc d/dz u
742  ! u_av <- u_av + dt d/dz visc d/dz u_av
743  call cpu_clock_begin(id_clock_vertvisc)
744  call vertvisc_coef(u, v, h, fluxes, visc, dt, g, gv, cs%vertvisc_CSp, cs%OBC)
745  call vertvisc(u, v, h, fluxes, visc, dt, cs%OBC, cs%ADp, cs%CDp, g, gv, &
746  cs%vertvisc_CSp, cs%taux_bot, cs%tauy_bot)
747  if (g%nonblocking_updates) then
748  call cpu_clock_end(id_clock_vertvisc) ; call cpu_clock_begin(id_clock_pass)
749  call start_group_pass(cs%pass_uv, g%Domain)
750  call cpu_clock_end(id_clock_pass) ; call cpu_clock_begin(id_clock_vertvisc)
751  endif
752  call vertvisc_remnant(visc, cs%visc_rem_u, cs%visc_rem_v, dt, g, gv, cs%vertvisc_CSp)
753  call cpu_clock_end(id_clock_vertvisc)
754  if (showcalltree) call calltree_waypoint("done with vertvisc (step_MOM_dyn_split_RK2)")
755 
756 ! Later, h_av = (h_in + h_out)/2, but for now use h_av to store h_in.
757  !$OMP parallel do default(shared)
758  do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2
759  h_av(i,j,k) = h(i,j,k)
760  enddo ; enddo ; enddo
761 
762  call cpu_clock_begin(id_clock_pass)
763  call do_group_pass(cs%pass_visc_rem, g%Domain)
764  if (g%nonblocking_updates) then
765  call complete_group_pass(cs%pass_uv, g%Domain)
766  else
767  call do_group_pass(cs%pass_uv, g%Domain)
768  endif
769  call cpu_clock_end(id_clock_pass)
770 
771  ! uh = u_av * h
772  ! h = h + dt * div . uh
773  ! u_av and v_av adjusted so their mass transports match uhbt and vhbt.
774  call cpu_clock_begin(id_clock_continuity)
775  call continuity(u, v, h, h, uh, vh, dt, g, gv, &
776  cs%continuity_CSp, cs%uhbt, cs%vhbt, cs%OBC, &
777  cs%visc_rem_u, cs%visc_rem_v, u_av, v_av)
778  call cpu_clock_end(id_clock_continuity)
779  call cpu_clock_begin(id_clock_pass)
780  call do_group_pass(cs%pass_h, g%Domain)
781  call cpu_clock_end(id_clock_pass)
782  ! Whenever thickness changes let the diag manager know, target grids
783  ! for vertical remapping may need to be regenerated.
784  call diag_update_remap_grids(cs%diag)
785  if (showcalltree) call calltree_waypoint("done with continuity (step_MOM_dyn_split_RK2)")
786 
787  call cpu_clock_begin(id_clock_pass)
788  if (g%nonblocking_updates) then
789  call start_group_pass(cs%pass_av_uvh, g%Domain)
790  else
791  call do_group_pass(cs%pass_av_uvh, g%domain)
792  endif
793  call cpu_clock_end(id_clock_pass)
794 
795  if (associated(cs%OBC)) then
796  call radiation_open_bdry_conds(cs%OBC, u, u_old_rad_obc, v, v_old_rad_obc, g, dt)
797  endif
798 
799 ! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in.
800  !$OMP parallel do default(shared)
801  do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2
802  h_av(i,j,k) = 0.5*(h_av(i,j,k) + h(i,j,k))
803  enddo ; enddo ; enddo
804 
805  if (g%nonblocking_updates) then
806  call cpu_clock_begin(id_clock_pass)
807  call complete_group_pass(cs%pass_av_uvh, g%Domain)
808  call cpu_clock_end(id_clock_pass)
809  endif
810  !$OMP parallel do default(shared)
811  do k=1,nz
812  do j=js-2,je+2 ; do i=isq-2,ieq+2
813  uhtr(i,j,k) = uhtr(i,j,k) + uh(i,j,k)*dt
814  enddo ; enddo
815  do j=jsq-2,jeq+2 ; do i=is-2,ie+2
816  vhtr(i,j,k) = vhtr(i,j,k) + vh(i,j,k)*dt
817  enddo ; enddo
818  enddo
819 
820  ! The time-averaged free surface height has already been set by the last
821  ! call to btstep.
822 
823  ! Here various terms used in to update the momentum equations are
824  ! offered for time averaging.
825  if (cs%id_PFu > 0) call post_data(cs%id_PFu, cs%PFu, cs%diag)
826  if (cs%id_PFv > 0) call post_data(cs%id_PFv, cs%PFv, cs%diag)
827  if (cs%id_CAu > 0) call post_data(cs%id_CAu, cs%CAu, cs%diag)
828  if (cs%id_CAv > 0) call post_data(cs%id_CAv, cs%CAv, cs%diag)
829 
830  ! Here the thickness fluxes are offered for time averaging.
831  if (cs%id_uh > 0) call post_data(cs%id_uh , uh, cs%diag)
832  if (cs%id_vh > 0) call post_data(cs%id_vh , vh, cs%diag)
833  if (cs%id_uav > 0) call post_data(cs%id_uav, u_av, cs%diag)
834  if (cs%id_vav > 0) call post_data(cs%id_vav, v_av, cs%diag)
835  if (cs%id_u_BT_accel > 0) call post_data(cs%id_u_BT_accel, cs%u_accel_bt, cs%diag)
836  if (cs%id_v_BT_accel > 0) call post_data(cs%id_v_BT_accel, cs%v_accel_bt, cs%diag)
837 
838  if (cs%debug) then
839  call mom_state_chksum("Corrector ", u, v, h, uh, vh, g, gv, symmetric=sym)
840  call uvchksum("Corrector avg [uv]", u_av, v_av, g%HI,haloshift=1, symmetric=sym)
841  call hchksum(h_av, "Corrector avg h", g%HI, haloshift=1, scale=gv%H_to_m)
842  ! call MOM_state_chksum("Corrector avg ", u_av, v_av, h_av, uh, vh, G, GV)
843  endif
844 
845  if (showcalltree) call calltree_leave("step_MOM_dyn_split_RK2()")
846 
Here is the call graph for this function:

Variable Documentation

◆ id_clock_btcalc

integer mom_dynamics_split_rk2::id_clock_btcalc
private

Definition at line 195 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

◆ id_clock_btforce

integer mom_dynamics_split_rk2::id_clock_btforce
private

Definition at line 195 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

◆ id_clock_btstep

integer mom_dynamics_split_rk2::id_clock_btstep
private

Definition at line 195 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

195 integer :: id_clock_btstep, id_clock_btcalc, id_clock_btforce

◆ id_clock_continuity

integer mom_dynamics_split_rk2::id_clock_continuity
private

Definition at line 194 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

194 integer :: id_clock_continuity, id_clock_thick_diff

◆ id_clock_cor

integer mom_dynamics_split_rk2::id_clock_cor

Definition at line 192 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

192 integer :: id_clock_cor, id_clock_pres, id_clock_vertvisc

◆ id_clock_horvisc

integer mom_dynamics_split_rk2::id_clock_horvisc
private

Definition at line 193 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

193 integer :: id_clock_horvisc, id_clock_mom_update

◆ id_clock_mom_update

integer mom_dynamics_split_rk2::id_clock_mom_update
private

Definition at line 193 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

◆ id_clock_pass

integer mom_dynamics_split_rk2::id_clock_pass
private

Definition at line 196 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

196 integer :: id_clock_pass, id_clock_pass_init

◆ id_clock_pass_init

integer mom_dynamics_split_rk2::id_clock_pass_init
private

Definition at line 196 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2().

◆ id_clock_pres

integer mom_dynamics_split_rk2::id_clock_pres
private

Definition at line 192 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().

◆ id_clock_thick_diff

integer mom_dynamics_split_rk2::id_clock_thick_diff
private

Definition at line 194 of file MOM_dynamics_split_RK2.F90.

◆ id_clock_vertvisc

integer mom_dynamics_split_rk2::id_clock_vertvisc
private

Definition at line 192 of file MOM_dynamics_split_RK2.F90.

Referenced by initialize_dyn_split_rk2(), and step_mom_dyn_split_rk2().