MOM6
MOM_continuity.F90
Go to the documentation of this file.
1 !> Solve the layer continuity equation.
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
9 use mom_diag_mediator, only : time_type, diag_ctrl
10 use mom_error_handler, only : mom_error, mom_mesg, fatal, warning, is_root_pe
13 use mom_grid, only : ocean_grid_type
15 use mom_variables, only : bt_cont_type
17 
18 implicit none ; private
19 
20 #include <MOM_memory.h>
21 
23 
24 !> Control structure for mom_continuity
25 type, public :: continuity_cs ; private
26  integer :: continuity_scheme !< Selects the discretization for the continuity solver.
27  !! Valid values are:
28  !! - PPM - A directionally split piecewise parabolic reconstruction solver.
29  !! The default, PPM, seems most appropriate for use with our current
30  !! time-splitting strategies.
31  type(continuity_ppm_cs), pointer :: ppm_csp => null() !< Control structure for mom_continuity_ppm
32 end type continuity_cs
33 
34 integer, parameter :: ppm_scheme = 1 !< Enumerated constant to select PPM
35 character(len=20), parameter :: ppm_string = "PPM" !< String to select PPM
36 
37 contains
38 
39 !> Time steps the layer thicknesses, using a monotonically limited, directionally split PPM scheme,
40 !! based on Lin (1994).
41 subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, &
42  visc_rem_u, visc_rem_v, u_cor, v_cor, &
43  uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont)
44  type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure.
45  type(verticalgrid_type), intent(in) :: GV !< Vertical grid structure.
46  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in) :: u !< Zonal velocity, in m/s.
47  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: v !< Meridional velocity, in m/s.
48  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: hin !< Initial layer thickness, in m or kg/m2.
49  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: h !< Final layer thickness, in m or kg/m2.
50  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(out) :: uh !< Volume flux through zonal faces =
51  !! u*h*dy, in m3/s.
52  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(out) :: vh !< Volume flux through meridional faces =
53  !! v*h*dx, in m3/s.
54  real, intent(in) :: dt !< Time increment, in s.
55  type(continuity_cs), pointer :: CS !< Control structure for mom_continuity.
56  real, dimension(SZIB_(G),SZJ_(G)), intent(in), optional :: uhbt !< The vertically summed volume
57  !! flux through zonal faces, in m3/s.
58  real, dimension(SZI_(G),SZJB_(G)), intent(in), optional :: vhbt !< The vertically summed volume
59  !! flux through meridional faces, in m3/s.
60  type(ocean_obc_type), pointer, optional :: OBC !< Open boundaries control structure.
61  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in), optional :: visc_rem_u !< Both the fraction of
62  !! zonal momentum that remains after a time-step of viscosity, and the fraction of a time-step's
63  !! worth of a barotropic acceleration that a layer experiences after viscosity is applied.
64  !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom).
65  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in), optional :: visc_rem_v !< Both the fraction of
66  !! meridional momentum that remains after a time-step of viscosity, and the fraction of a time-step's
67  !! worth of a barotropic acceleration that a layer experiences after viscosity is applied.
68  !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom).
69  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(out), optional :: u_cor !< The zonal velocities that
70  !! give uhbt as the depth-integrated transport, in m/s.
71  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(out), optional :: v_cor !< The meridional velocities that
72  !! give vhbt as the depth-integrated transport, in m/s.
73  real, dimension(SZIB_(G),SZJ_(G)), intent(in), optional :: uhbt_aux !< A second summed zonal
74  !! volume flux in m3/s.
75  real, dimension(SZI_(G),SZJB_(G)), intent(in), optional :: vhbt_aux !< A second summed meridional
76  !! volume flux in m3/s.
77  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(inout), optional :: u_cor_aux !< The zonal velocities
78  !! that give uhbt_aux as the depth-integrated transport, in m/s.
79  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(inout), optional :: v_cor_aux !< The meridional velocities
80  !! that give vhbt_aux as the depth-integrated transport, in m/s.
81  type(bt_cont_type), pointer, optional :: BT_cont !< A structure with elements
82  !! that describe the effective open face areas as a function of barotropic flow.
83 
84  if (present(visc_rem_u) .neqv. present(visc_rem_v)) call mom_error(fatal, &
85  "MOM_continuity: Either both visc_rem_u and visc_rem_v or neither"// &
86  " one must be present in call to continuity.")
87  if (present(u_cor) .neqv. present(v_cor)) call mom_error(fatal, &
88  "MOM_continuity: Either both u_cor and v_cor or neither"// &
89  " one must be present in call to continuity.")
90  if (present(uhbt_aux) .neqv. present(vhbt_aux)) call mom_error(fatal, &
91  "MOM_continuity: Either both uhbt_aux and uhbt_aux or neither"// &
92  " one must be present in call to continuity.")
93  if (present(u_cor_aux) .neqv. present(v_cor_aux)) call mom_error(fatal, &
94  "MOM_continuity: Either both u_cor_aux and v_cor_aux or neither"// &
95  " one must be present in call to continuity.")
96  if (present(u_cor_aux) .neqv. present(uhbt_aux)) call mom_error(fatal, &
97  "MOM_continuity: u_cor_aux can only be calculated if uhbt_aux is"// &
98  " provided, and uhbt_aux has no other purpose. Include both arguments"//&
99  " or neither.")
100 
101  if (cs%continuity_scheme == ppm_scheme) then
102  call continuity_ppm(u, v, hin, h, uh, vh, dt, g, gv, cs%PPM_CSp, uhbt, vhbt, obc, &
103  visc_rem_u, visc_rem_v, u_cor, v_cor, &
104  uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, bt_cont)
105  else
106  call mom_error(fatal, "continuity: Unrecognized value of continuity_scheme")
107  endif
108 
109 end subroutine continuity
110 
111 !> Initializes continuity_cs
112 subroutine continuity_init(Time, G, GV, param_file, diag, CS)
113  type(time_type), target, intent(in) :: Time !< Current model time.
114  type(ocean_grid_type), intent(in) :: G !< Ocean grid structure.
115  type(verticalgrid_type), intent(in) :: GV !< Vertical grid structure.
116  type(param_file_type), intent(in) :: param_file !< Parameter file handles.
117  type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure.
118  type(continuity_cs), pointer :: CS !< Control structure for mom_continuity.
119 ! This include declares and sets the variable "version".
120 #include "version_variable.h"
121  character(len=40) :: mdl = "MOM_continuity" ! This module's name.
122  character(len=20) :: tmpstr
123 
124  if (associated(cs)) then
125  call mom_error(warning, "continuity_init called with associated control structure.")
126  return
127  endif
128  allocate(cs)
129 
130  ! Read all relevant parameters and write them to the model log.
131  call log_version(param_file, mdl, version, "")
132  call get_param(param_file, mdl, "CONTINUITY_SCHEME", tmpstr, &
133  "CONTINUITY_SCHEME selects the discretization for the \n"//&
134  "continuity solver. The only valid value currently is: \n"//&
135  "\t PPM - use a positive-definite (or monotonic) \n"//&
136  "\t piecewise parabolic reconstruction solver.", &
137  default=ppm_string)
138 
139  tmpstr = uppercase(tmpstr) ; cs%continuity_scheme = 0
140  select case (trim(tmpstr))
141  case (ppm_string) ; cs%continuity_scheme = ppm_scheme
142  case default
143  call mom_mesg('continuity_init: CONTINUITY_SCHEME ="'//trim(tmpstr)//'"', 0)
144  call mom_mesg("continuity_init: The only valid value is currently "// &
145  trim(ppm_string), 0)
146  call mom_error(fatal, "continuity_init: Unrecognized setting "// &
147  "#define CONTINUITY_SCHEME "//trim(tmpstr)//" found in input file.")
148  end select
149 
150  if (cs%continuity_scheme == ppm_scheme) then
151  call continuity_ppm_init(time, g, gv, param_file, diag, cs%PPM_CSp)
152  endif
153 
154 end subroutine continuity_init
155 
156 
157 !> continuity_stencil returns the continuity solver stencil size
158 function continuity_stencil(CS) result(stencil)
159  type(continuity_cs), pointer :: CS !< Module's control structure.
160  integer :: stencil !< The continuity solver stencil size with the current settings.
161 
162  stencil = 1
163 
164  if (cs%continuity_scheme == ppm_scheme) then
165  stencil = continuity_ppm_stencil(cs%PPM_CSp)
166  endif
167 
168 end function continuity_stencil
169 
170 !> Destructor for continuity_cs.
171 subroutine continuity_end(CS)
172  type(continuity_cs), pointer :: CS !< Control structure for mom_continuity.
173 
174  if (cs%continuity_scheme == ppm_scheme) then
175  call continuity_ppm_end(cs%PPM_CSp)
176  endif
177 
178  deallocate(cs)
179 
180 end subroutine continuity_end
181 
182 end module mom_continuity
integer, parameter ppm_scheme
Enumerated constant to select PPM.
subroutine, public continuity_init(Time, G, GV, param_file, diag, CS)
Initializes continuity_cs.
integer function, public continuity_ppm_stencil(CS)
continuity_PPM_stencil returns the continuity solver stencil size
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Solve the layer continuity equation.
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public continuity_ppm(u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, visc_rem_u, visc_rem_v, u_cor, v_cor, uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont)
Time steps the layer thicknesses, using a monotonically limit, directionally split PPM scheme...
The BT_cont_type structure contains information about the summed layer transports and how they will v...
Control structure for mom_continuity_ppm.
character(len=len(input_string)) function, public uppercase(input_string)
Control structure for mom_continuity.
logical function, public is_root_pe()
subroutine, public continuity_ppm_end(CS)
Destructor for continuity_ppm_cs.
character(len=20), parameter ppm_string
String to select PPM.
subroutine, public mom_mesg(message, verb, all_print)
integer function, public continuity_stencil(CS)
continuity_stencil returns the continuity solver stencil size
subroutine, public continuity(u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, visc_rem_u, visc_rem_v, u_cor, v_cor, uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont)
Time steps the layer thicknesses, using a monotonically limited, directionally split PPM scheme...
Solve the layer continuity equation using the PPM method for layer fluxes.
Controls where open boundary conditions are applied.
subroutine, public continuity_end(CS)
Destructor for continuity_cs.
subroutine, public mom_error(level, message, all_print)
subroutine, public continuity_ppm_init(Time, G, GV, param_file, diag, CS)
Initializes continuity_ppm_cs.