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