MOM6
MOM_variables.F90
Go to the documentation of this file.
2 
3 !***********************************************************************
4 !* GNU General Public License *
5 !* This file is a part of MOM. *
6 !* *
7 !* MOM is free software; you can redistribute it and/or modify it and *
8 !* are expected to follow the terms of the GNU General Public License *
9 !* as published by the Free Software Foundation; either version 2 of *
10 !* the License, or (at your option) any later version. *
11 !* *
12 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
13 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
14 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
15 !* License for more details. *
16 !* *
17 !* For the full text of the GNU General Public License, *
18 !* write to: Free Software Foundation, Inc., *
19 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
20 !* or see: http://www.gnu.org/licenses/gpl.html *
21 !***********************************************************************
22 
23 use mom_domains, only : mom_domain_type, get_domain_extent, group_pass_type
24 use mom_debugging, only : hchksum
25 use mom_error_handler, only : mom_error, fatal
26 use mom_grid, only : ocean_grid_type
27 use mom_io, only : vardesc
28 use mom_eos, only : eos_type
29 
31 
32 implicit none ; private
33 
34 #include <MOM_memory.h>
35 
38 
39 type, public :: p3d
40  real, dimension(:,:,:), pointer :: p => null()
41 end type p3d
42 type, public :: p2d
43  real, dimension(:,:), pointer :: p => null()
44 end type p2d
45 
46 !> The following structure contains pointers to various fields
47 !! which may be used describe the surface state of MOM, and which
48 !! will be returned to a the calling program
49 type, public :: surface
50  real, allocatable, dimension(:,:) :: &
51  sst, & !< The sea surface temperature in C.
52  sss, & !< The sea surface salinity in psu.
53  sfc_density, & !< The mixed layer density in kg m-3.
54  hml, & !< The mixed layer depth in m.
55  u, & !< The mixed layer zonal velocity in m s-1.
56  v, & !< The mixed layer meridional velocity in m s-1.
57  sea_lev, & !< The sea level in m. If a reduced surface gravity is
58  !! used, that is compensated for in sea_lev.
59  ocean_mass, & !< The total mass of the ocean in kg m-2.
60  ocean_heat, & !< The total heat content of the ocean in C kg m-2.
61  ocean_salt, & !< The total salt content of the ocean in kgSalt m-2.
62  salt_deficit !< The salt needed to maintain the ocean column at a minimum
63  !! salinity of 0.01 PSU over the call to step_MOM, in kgSalt m-2.
64  real, pointer, dimension(:,:) :: &
65  taux_shelf => null(), & !< The zonal and meridional stresses on the ocean
66  tauy_shelf => null(), & !< under shelves, in Pa.
67  frazil => null(), & !< The energy needed to heat the ocean column to the
68  !! freezing point over the call to step_MOM, in J m-2.
69  tempxpme => null(), & !< The net inflow of water into the ocean times
70  !! the temperature at which this inflow occurs during
71  !! the call to step_MOM, in deg C kg m-2.
72  !! This should be prescribed in the forcing fields,
73  !! but as it often is not, this is a useful heat budget
74  !! diagnostic.
75  internal_heat => null() !< Any internal or geothermal heat sources that
76  !! are applied to the ocean integrated over the call
77  !! to step_MOM, in deg C kg m-2.
78  type(coupler_2d_bc_type), pointer :: &
79  tr_fields => null() ! NOTE: ALL OF THE ARRAYS IN TR_FIELDS USE THE COUPLER'S INDEXING! CONVENTION AND HAVE NO HALOS! THIS IS DONE TO CONFORM TO! THE TREATMENT IN MOM4, BUT I DON'T LIKE IT!!< A structure that may contain an array of named
80  !! fields describing tracer-related quantities.
81  !!
82  !!
83  !!
84  logical :: arrays_allocated = .false. !< A flag that indicates whether
85  !! the surface type has had its memory allocated.
86 end type surface
87 
88 !> The thermo_var_ptrs structure contains pointers to an assortment of
89 !! thermodynamic fields that may be available, including potential temperature,
90 !! salinity, heat capacity, and the equation of state control structure.
91 type, public :: thermo_var_ptrs
92 ! If allocated, the following variables have nz layers.
93  real, pointer :: t(:,:,:) => null() !< Potential temperature in C.
94  real, pointer :: s(:,:,:) => null() !< Salnity in psu or ppt.
95  type(eos_type), pointer :: eqn_of_state => null() !< Type that indicates the
96  !! equation of state to use.
97  real :: p_ref !< The coordinate-density reference pressure in Pa.
98  !! This is the pressure used to calculate Rml from
99  !! T and S when eqn_of_state is associated.
100  real :: c_p !< The heat capacity of seawater, in J K-1 kg-1.
101  !! When conservative temperature is used, this is
102  !! constant and exactly 3991.86795711963 J K kg-1.
103  real, pointer, dimension(:,:) :: &
104 ! These arrays are accumulated fluxes for communication with other components.
105  frazil => null(), & !< The energy needed to heat the ocean column to the
106  !! freezing point since calculate_surface_state was
107  !! last called, in units of J m-2.
108  salt_deficit => null(), & !< The salt needed to maintain the ocean column
109  !! at a minumum salinity of 0.01 PSU since the last time
110  !! that calculate_surface_state was called, in units
111  !! of gSalt m-2.
112  tempxpme => null(), & !< The net inflow of water into the ocean times the
113  !! temperature at which this inflow occurs since the
114  !! last call to calculate_surface_state, in units of
115  !! deg C kg m-2. This should be prescribed in the
116  !! forcing fields, but as it often is not, this is a
117  !! useful heat budget diagnostic.
118  internal_heat => null() !< Any internal or geothermal heat sources that
119  !! have been applied to the ocean since the last call to
120  !! calculate_surface_state, in units of deg C kg m-2.
121 end type thermo_var_ptrs
122 
123 !> The ocean_internal_state structure contains pointers to all of the prognostic
124 !! variables allocated in MOM_variables.F90 and MOM.F90. It is useful for
125 !! sending these variables for diagnostics, and in preparation for ensembles
126 !! later on. All variables have the same names as the local (public) variables
127 !! they refer to in MOM.F90.
128 type, public :: ocean_internal_state
129  real, pointer, dimension(:,:,:) :: &
130  u => null(), v => null(), h => null()
131  real, pointer, dimension(:,:,:) :: &
132  uh => null(), vh => null(), &
133  cau => null(), cav => null(), &
134  pfu => null(), pfv => null(), diffu => null(), diffv => null(), &
135  t => null(), s => null(), &
136  pbce => null(), u_accel_bt => null(), v_accel_bt => null(), &
137  u_av => null(), v_av => null(), u_prev => null(), v_prev => null()
138 end type ocean_internal_state
139 
140 !> The accel_diag_ptrs structure contains pointers to arrays with accelerations,
141 !! which can later be used for derived diagnostics, like energy balances.
142 type, public :: accel_diag_ptrs
143 
144 ! Each of the following fields has nz layers.
145  real, pointer :: diffu(:,:,:) => null() ! Accelerations due to along iso-
146  real, pointer :: diffv(:,:,:) => null() ! pycnal viscosity, in m s-2.
147  real, pointer :: cau(:,:,:) => null() ! Coriolis and momentum advection
148  real, pointer :: cav(:,:,:) => null() ! accelerations, in m s-2.
149  real, pointer :: pfu(:,:,:) => null() ! Accelerations due to pressure
150  real, pointer :: pfv(:,:,:) => null() ! forces, in m s-2.
151  real, pointer :: du_dt_visc(:,:,:) => null()! Accelerations due to vertical
152  real, pointer :: dv_dt_visc(:,:,:) => null()! viscosity, in m s-2.
153  real, pointer :: du_dt_dia(:,:,:) => null()! Accelerations due to diapycnal
154  real, pointer :: dv_dt_dia(:,:,:) => null()! mixing, in m s-2.
155  real, pointer :: du_other(:,:,:) => null() ! Velocity changes due to any other
156  real, pointer :: dv_other(:,:,:) => null() ! processes that are not due to any
157  ! explicit accelerations, in m s-1.
158 
159  ! These accelerations are sub-terms included in the accelerations above.
160  real, pointer :: gradkeu(:,:,:) => null() ! gradKEu = - d/dx(u2), in m s-2.
161  real, pointer :: gradkev(:,:,:) => null() ! gradKEv = - d/dy(u2), in m s-2.
162  real, pointer :: rv_x_v(:,:,:) => null() ! rv_x_v = rv * v at u, in m s-2.
163  real, pointer :: rv_x_u(:,:,:) => null() ! rv_x_u = rv * u at v, in m s-2.
164 
165 end type accel_diag_ptrs
166 
167 !> The cont_diag_ptrs structure contains pointers to arrays with transports,
168 !! which can later be used for derived diagnostics, like energy balances.
169 type, public :: cont_diag_ptrs
170 
171 ! Each of the following fields has nz layers.
172  real, pointer :: uh(:,:,:) => null() ! Resolved layer thickness fluxes,
173  real, pointer :: vh(:,:,:) => null() ! in m3 s-1 or kg s-1.
174  real, pointer :: uhgm(:,:,:) => null() ! Thickness diffusion induced
175  real, pointer :: vhgm(:,:,:) => null() ! volume fluxes in m3 s-1.
176 
177 ! Each of the following fields is found at nz+1 interfaces.
178  real, pointer :: diapyc_vel(:,:,:) => null()! The net diapycnal velocity,
179 
180 end type cont_diag_ptrs
181 
182 !> The vertvisc_type structure contains vertical viscosities, drag
183 !! coefficients, and related fields.
184 type, public :: vertvisc_type
185  real :: prandtl_turb !< The Prandtl number for the turbulent diffusion
186  !! that is captured in Kd_turb.
187  real, pointer, dimension(:,:) :: &
188  bbl_thick_u => null(), & !< The bottom boundary layer thickness at the
189  !! u-points, in m.
190  bbl_thick_v => null(), & !< The bottom boundary layer thickness at the
191  !! v-points, in m.
192  kv_bbl_u => null(), & !< The bottom boundary layer viscosity at the
193  !! u-points, in m2 s-1.
194  kv_bbl_v => null(), & !< The bottom boundary layer viscosity at the
195  !! v-points, in m2 s-1.
196  ustar_bbl => null(), & !< The turbulence velocity in the bottom boundary
197  !! layer at h points, in m s-1.
198  tke_bbl => null(), & !< A term related to the bottom boundary layer
199  !! source of turbulent kinetic energy, currently
200  !! in units of m3 s-3, but will later be changed
201  !! to W m-2.
202  taux_shelf => null(), & !< The zonal stresses on the ocean under shelves, in Pa.
203  tauy_shelf => null(), & !< The meridional stresses on the ocean under shelves, in Pa.
204  tbl_thick_shelf_u => null(), & !< Thickness of the viscous top boundary
205  !< layer under ice shelves at u-points, in m.
206  tbl_thick_shelf_v => null(), & !< Thickness of the viscous top boundary
207  !< layer under ice shelves at v-points, in m.
208  kv_tbl_shelf_u => null(), & !< Viscosity in the viscous top boundary layer
209  !! under ice shelves at u-points, in m2 s-1.
210  kv_tbl_shelf_v => null(), & !< Viscosity in the viscous top boundary layer
211  !! under ice shelves at u-points, in m2 s-1.
212  nkml_visc_u => null(), & !< The number of layers in the viscous surface
213  !! mixed layer at u-points (nondimensional). This
214  !! is not an integer because there may be
215  !! fractional layers, and it is stored
216  !! in terms of layers, not depth, to facilitate
217  !! the movement of the viscous boundary layer with
218  !! the flow.
219  nkml_visc_v => null(), & !< The number of layers in the viscous surface
220  !! mixed layer at v-points (nondimensional).
221  mld => null() !< Instantaneous active mixing layer depth (H units).
222  real, pointer, dimension(:,:,:) :: &
223  ray_u => null(), & !< The Rayleigh drag velocity to be applied to each layer
224  !! at u-points, in m s-1.
225  ray_v => null(), & !< The Rayleigh drag velocity to be applied to each layer
226  !! at v-points, in m s-1.
227  kd_extra_t => null(), & !< The extra diffusivity of temperature due to
228  !! double diffusion relative to the diffusivity of
229  !! density, in m2 s-1.
230  kd_extra_s => null(), & !< The extra diffusivity of salinity due to
231  !! double diffusion relative to the diffusivity of
232  !! density, in m2 s-1.
233  ! One of Kd_extra_T and Kd_extra_S is always 0.
234  ! Kd_extra_S is positive for salt fingering; Kd_extra_T
235  ! is positive for double diffusive convection. These
236  ! are only allocated if DOUBLE_DIFFUSION is true.
237  kd_turb => null(), &!< The turbulent diapycnal diffusivity at the interfaces
238  !! between each layer, in m2 s-1.
239  kv_turb => null(), &!< The turbulent vertical viscosity at the interfaces
240  !! between each layer, in m2 s-1.
241  tke_turb => null() !< The turbulent kinetic energy per unit mass defined
242  !! at the interfaces between each layer, in m2 s-2.
243 end type vertvisc_type
244 
245 !> The BT_cont_type structure contains information about the summed layer
246 !! transports and how they will vary as the barotropic velocity is changed.
247 type, public :: bt_cont_type
248  real, pointer, dimension(:,:) :: &
249  fa_u_ee => null(), & ! The FA_u_XX variables are the effective open face
250  fa_u_e0 => null(), & ! areas for barotropic transport through the zonal
251  fa_u_w0 => null(), & ! faces, all in H m, with the XX indicating where
252  fa_u_ww => null(), & ! the transport is from, with _EE drawing from points
253  ! far to the east, _E0 from points nearby from the
254  ! east, _W0 nearby from the west, and _WW from far to
255  ! the west.
256  ubt_ww => null(), & ! uBT_WW is the barotropic velocity, in m s-1, beyond
257  ! which the marginal open face area is FA_u_WW.
258  ! uBT_EE must be non-negative.
259  ubt_ee => null(), & ! uBT_EE is the barotropic velocity, in m s-1, beyond
260  ! which the marginal open face area is FA_u_EE.
261  ! uBT_EE must be non-positive.
262  fa_v_nn => null(), & ! The FA_v_XX variables are the effective open face
263  fa_v_n0 => null(), & ! areas for barotropic transport through the meridional
264  fa_v_s0 => null(), & ! faces, all in H m, with the XX indicating where
265  fa_v_ss => null(), & ! the transport is from, with _NN drawing from points
266  ! far to the north, _N0 from points nearby from the
267  ! north, _S0 nearby from the south, and _SS from far
268  ! to the south.
269  vbt_ss => null(), & ! vBT_SS is the barotropic velocity, in m s-1, beyond
270  ! which the marginal open face area is FA_v_SS.
271  ! vBT_SS must be non-negative.
272  vbt_nn => null() ! vBT_NN is the barotropic velocity, in m s-1, beyond
273  ! which the marginal open face area is FA_v_NN.
274  ! vBT_NN must be non-positive.
275  real, pointer, dimension(:,:,:) :: &
276  h_u => null(), & ! An effective thickness at zonal faces, in H.
277  h_v => null() ! An effective thickness at meridional faces, in H.
278  type(group_pass_type) :: pass_polarity_bt, pass_fa_uv ! For group halo updates
279 end type bt_cont_type
280 
281 contains
282 
283 !> alloc_BT_cont_type allocates the arrays contained within a BT_cont_type and
284 !! initializes them to 0.
285 subroutine alloc_bt_cont_type(BT_cont, G, alloc_faces)
286  type(bt_cont_type), pointer :: BT_cont
287  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
288  logical, optional, intent(in) :: alloc_faces
289 
290  integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
291  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
292  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
293 
294  if (associated(bt_cont)) call mom_error(fatal, &
295  "alloc_BT_cont_type called with an associated BT_cont_type pointer.")
296 
297  allocate(bt_cont)
298  allocate(bt_cont%FA_u_WW(isdb:iedb,jsd:jed)) ; bt_cont%FA_u_WW(:,:) = 0.0
299  allocate(bt_cont%FA_u_W0(isdb:iedb,jsd:jed)) ; bt_cont%FA_u_W0(:,:) = 0.0
300  allocate(bt_cont%FA_u_E0(isdb:iedb,jsd:jed)) ; bt_cont%FA_u_E0(:,:) = 0.0
301  allocate(bt_cont%FA_u_EE(isdb:iedb,jsd:jed)) ; bt_cont%FA_u_EE(:,:) = 0.0
302  allocate(bt_cont%uBT_WW(isdb:iedb,jsd:jed)) ; bt_cont%uBT_WW(:,:) = 0.0
303  allocate(bt_cont%uBT_EE(isdb:iedb,jsd:jed)) ; bt_cont%uBT_EE(:,:) = 0.0
304 
305  allocate(bt_cont%FA_v_SS(isd:ied,jsdb:jedb)) ; bt_cont%FA_v_SS(:,:) = 0.0
306  allocate(bt_cont%FA_v_S0(isd:ied,jsdb:jedb)) ; bt_cont%FA_v_S0(:,:) = 0.0
307  allocate(bt_cont%FA_v_N0(isd:ied,jsdb:jedb)) ; bt_cont%FA_v_N0(:,:) = 0.0
308  allocate(bt_cont%FA_v_NN(isd:ied,jsdb:jedb)) ; bt_cont%FA_v_NN(:,:) = 0.0
309  allocate(bt_cont%vBT_SS(isd:ied,jsdb:jedb)) ; bt_cont%vBT_SS(:,:) = 0.0
310  allocate(bt_cont%vBT_NN(isd:ied,jsdb:jedb)) ; bt_cont%vBT_NN(:,:) = 0.0
311 
312  if (present(alloc_faces)) then ; if (alloc_faces) then
313  allocate(bt_cont%h_u(isdb:iedb,jsd:jed,1:g%ke)) ; bt_cont%h_u(:,:,:) = 0.0
314  allocate(bt_cont%h_v(isd:ied,jsdb:jedb,1:g%ke)) ; bt_cont%h_v(:,:,:) = 0.0
315  endif ; endif
316 
317 end subroutine alloc_bt_cont_type
318 
319 !> dealloc_BT_cont_type deallocates the arrays contained within a BT_cont_type.
320 subroutine dealloc_bt_cont_type(BT_cont)
321  type(bt_cont_type), pointer :: BT_cont
322 
323  if (.not.associated(bt_cont)) return
324 
325  deallocate(bt_cont%FA_u_WW) ; deallocate(bt_cont%FA_u_W0)
326  deallocate(bt_cont%FA_u_E0) ; deallocate(bt_cont%FA_u_EE)
327  deallocate(bt_cont%uBT_WW) ; deallocate(bt_cont%uBT_EE)
328 
329  deallocate(bt_cont%FA_v_SS) ; deallocate(bt_cont%FA_v_S0)
330  deallocate(bt_cont%FA_v_N0) ; deallocate(bt_cont%FA_v_NN)
331  deallocate(bt_cont%vBT_SS) ; deallocate(bt_cont%vBT_NN)
332 
333  if (associated(bt_cont%h_u)) deallocate(bt_cont%h_u)
334  if (associated(bt_cont%h_v)) deallocate(bt_cont%h_v)
335 
336  deallocate(bt_cont)
337 
338 end subroutine dealloc_bt_cont_type
339 
340 !> MOM_thermovar_chksum does diagnostic checksums on various elements of a
341 !! thermo_var_ptrs type for debugging.
342 subroutine mom_thermovar_chksum(mesg, tv, G)
343  character(len=*), intent(in) :: mesg
344  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic variables
345  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
346 ! This subroutine writes out chksums for the model's basic state variables.
347 ! Arguments: mesg - A message that appears on the chksum lines.
348 ! (in) u - Zonal velocity, in m s-1.
349 ! (in) v - Meridional velocity, in m s-1.
350 ! (in) h - Layer thickness, in m.
351 ! (in) uh - Volume flux through zonal faces = u*h*dy, m3 s-1.
352 ! (in) vh - Volume flux through meridional faces = v*h*dx, in m3 s-1.
353 ! (in) G - The ocean's grid structure.
354  integer :: is, ie, js, je, nz
355  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
356 
357  ! Note that for the chksum calls to be useful for reproducing across PE
358  ! counts, there must be no redundant points, so all variables use is..ie
359  ! and js...je as their extent.
360  if (associated(tv%T)) &
361  call hchksum(tv%T, mesg//" tv%T",g%HI)
362  if (associated(tv%S)) &
363  call hchksum(tv%S, mesg//" tv%S",g%HI)
364  if (associated(tv%frazil)) &
365  call hchksum(tv%frazil, mesg//" tv%frazil",g%HI)
366  if (associated(tv%salt_deficit)) &
367  call hchksum(tv%salt_deficit, mesg//" tv%salt_deficit",g%HI)
368  if (associated(tv%TempxPmE)) &
369  call hchksum(tv%TempxPmE, mesg//" tv%TempxPmE",g%HI)
370 end subroutine mom_thermovar_chksum
371 
372 end module mom_variables
The following structure contains pointers to various fields which may be used describe the surface st...
subroutine, public alloc_bt_cont_type(BT_cont, G, alloc_faces)
alloc_BT_cont_type allocates the arrays contained within a BT_cont_type and initializes them to 0...
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
subroutine, public mom_thermovar_chksum(mesg, tv, G)
MOM_thermovar_chksum does diagnostic checksums on various elements of a thermo_var_ptrs type for debu...
Provides the ocean grid type.
Definition: MOM_grid.F90:2
The vertvisc_type structure contains vertical viscosities, drag coefficients, and related fields...
This module contains I/O framework code.
Definition: MOM_io.F90:2
The accel_diag_ptrs structure contains pointers to arrays with accelerations, which can later be used...
The BT_cont_type structure contains information about the summed layer transports and how they will v...
subroutine, public dealloc_bt_cont_type(BT_cont)
dealloc_BT_cont_type deallocates the arrays contained within a BT_cont_type.
The cont_diag_ptrs structure contains pointers to arrays with transports, which can later be used for...
The ocean_internal_state structure contains pointers to all of the prognostic variables allocated in ...
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
Type for describing a variable, typically a tracer.
Definition: MOM_io.F90:51
The MOM_domain_type contains information about the domain decompositoin.
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine, public get_domain_extent(Domain, isc, iec, jsc, jec, isd, ied, jsd, jed, isg, ieg, jsg, jeg, idg_offset, jdg_offset, symmetric, local_indexing, index_offset)
subroutine, public mom_error(level, message, all_print)
A control structure for the equation of state.
Definition: MOM_EOS.F90:55