MOM6
MOM_tracer_flow_control.F90
Go to the documentation of this file.
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
22 !********+*********+*********+*********+*********+*********+*********+**
23 !* *
24 !* By Will Cooke, April 2003 *
25 !* *
26 !* This module contains two subroutines into which calls to other *
27 !* tracer initialization (call_tracer_init_fns) and column physics *
28 !* routines (call_tracer_column_fns) can be inserted. *
29 !* *
30 !********+*********+*********+*********+*********+*********+*********+**
31 
32 use mom_diag_mediator, only : time_type, diag_ctrl
33 use mom_diag_to_z, only : diag_to_z_cs
34 use mom_error_handler, only : mom_error, fatal, warning
36 use mom_forcing_type, only : forcing, optics_type
37 use mom_grid, only : ocean_grid_type
38 use mom_hor_index, only : hor_index_type
40 use mom_restart, only : mom_restart_cs
41 use mom_sponge, only : sponge_cs
42 use mom_ale_sponge, only : ale_sponge_cs
46 #include <MOM_memory.h>
47 
48 ! Add references to other user-provide tracer modules here.
73 #ifdef _USE_GENERIC_TRACER
74 use mom_generic_tracer, only : register_mom_generic_tracer, initialize_mom_generic_tracer
75 use mom_generic_tracer, only : mom_generic_tracer_column_physics, mom_generic_tracer_surface_state
76 use mom_generic_tracer, only : end_mom_generic_tracer, mom_generic_tracer_get
77 use mom_generic_tracer, only : mom_generic_tracer_stock, mom_generic_tracer_min_max, mom_generic_tracer_cs
78 #endif
86 
87 implicit none ; private
88 
92 
93 type, public :: tracer_flow_control_cs ; private
94  logical :: use_user_tracer_example = .false.
95  logical :: use_dome_tracer = .false.
96  logical :: use_isomip_tracer = .false.
97  logical :: use_ideal_age = .false.
98  logical :: use_regional_dyes = .false.
99  logical :: use_oil = .false.
100  logical :: use_advection_test_tracer = .false.
101  logical :: use_ocmip2_cfc = .false.
102  logical :: use_mom_generic_tracer = .false.
103  logical :: use_pseudo_salt_tracer = .false.
104  logical :: use_boundary_impulse_tracer = .false.
105  type(user_tracer_example_cs), pointer :: user_tracer_example_csp => null()
106  type(dome_tracer_cs), pointer :: dome_tracer_csp => null()
107  type(isomip_tracer_cs), pointer :: isomip_tracer_csp => null()
108  type(ideal_age_tracer_cs), pointer :: ideal_age_tracer_csp => null()
109  type(dye_tracer_cs), pointer :: dye_tracer_csp => null()
110  type(oil_tracer_cs), pointer :: oil_tracer_csp => null()
111  type(advection_test_tracer_cs), pointer :: advection_test_tracer_csp => null()
112  type(ocmip2_cfc_cs), pointer :: ocmip2_cfc_csp => null()
113 #ifdef _USE_GENERIC_TRACER
114  type(mom_generic_tracer_cs), pointer :: mom_generic_tracer_csp => null()
115 #endif
116  type(pseudo_salt_tracer_cs), pointer :: pseudo_salt_tracer_csp => null()
117  type(boundary_impulse_tracer_cs), pointer :: boundary_impulse_tracer_csp => null()
118 end type tracer_flow_control_cs
119 
120 contains
121 
122 !> The following 5 subroutines and associated definitions provide the
123 !! machinery to register and call the subroutines that initialize
124 !! tracers and apply vertical column processes to tracers.
125 subroutine call_tracer_register(HI, GV, param_file, CS, tr_Reg, restart_CS)
126  type(hor_index_type), intent(in) :: HI !< A horizontal index type structure.
127  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
128  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time
129  !! parameters.
130  type(tracer_flow_control_cs), pointer :: CS !< A pointer that is set to point to the
131  !! control structure for this module.
132  type(tracer_registry_type), pointer :: tr_Reg !< A pointer that is set to point to the
133  !! control structure for the tracer
134  !! advection and diffusion module.
135  type(mom_restart_cs), pointer :: restart_CS !< A pointer to the restart control
136  !! structure.
137 ! Arguments: HI - A horizontal index type structure.
138 ! (in) GV - The ocean's vertical grid structure.
139 ! (in) param_file - A structure indicating the open file to parse for
140 ! model parameter values.
141 ! (in/out) CS - A pointer that is set to point to the control structure
142 ! for this module
143 ! (in/out) tr_Reg - A pointer that is set to point to the control structure
144 ! for the tracer advection and diffusion module.
145 ! (in) restart_CS - A pointer to the restart control structure.
146 
147 ! This include declares and sets the variable "version".
148 #include "version_variable.h"
149  character(len=40) :: mdl = "MOM_tracer_flow_control" ! This module's name.
150 
151  if (associated(cs)) then
152  call mom_error(warning, "call_tracer_register called with an associated "// &
153  "control structure.")
154  return
155  else ; allocate(cs) ; endif
156 
157  ! Read all relevant parameters and write them to the model log.
158  call log_version(param_file, mdl, version, "")
159  call get_param(param_file, mdl, "USE_USER_TRACER_EXAMPLE", &
160  cs%use_USER_tracer_example, &
161  "If true, use the USER_tracer_example tracer package.", &
162  default=.false.)
163  call get_param(param_file, mdl, "USE_DOME_TRACER", cs%use_DOME_tracer, &
164  "If true, use the DOME_tracer tracer package.", &
165  default=.false.)
166  call get_param(param_file, mdl, "USE_ISOMIP_TRACER", cs%use_ISOMIP_tracer, &
167  "If true, use the ISOMIP_tracer tracer package.", &
168  default=.false.)
169  call get_param(param_file, mdl, "USE_IDEAL_AGE_TRACER", cs%use_ideal_age, &
170  "If true, use the ideal_age_example tracer package.", &
171  default=.false.)
172  call get_param(param_file, mdl, "USE_REGIONAL_DYES", cs%use_regional_dyes, &
173  "If true, use the regional_dyes tracer package.", &
174  default=.false.)
175  call get_param(param_file, mdl, "USE_OIL_TRACER", cs%use_oil, &
176  "If true, use the oil_tracer tracer package.", &
177  default=.false.)
178  call get_param(param_file, mdl, "USE_ADVECTION_TEST_TRACER", cs%use_advection_test_tracer, &
179  "If true, use the advection_test_tracer tracer package.", &
180  default=.false.)
181  call get_param(param_file, mdl, "USE_OCMIP2_CFC", cs%use_OCMIP2_CFC, &
182  "If true, use the MOM_OCMIP2_CFC tracer package.", &
183  default=.false.)
184  call get_param(param_file, mdl, "USE_generic_tracer", &
185  cs%use_MOM_generic_tracer, &
186  "If true and _USE_GENERIC_TRACER is defined as a \n"//&
187  "preprocessor macro, use the MOM_generic_tracer packages.", &
188  default=.false.)
189  call get_param(param_file, mdl, "USE_PSEUDO_SALT_TRACER", cs%use_pseudo_salt_tracer, &
190  "If true, use the pseudo salt tracer, typically run as a diagnostic.", &
191  default=.false.)
192  call get_param(param_file, mdl, "USE_BOUNDARY_IMPULSE_TRACER", cs%use_boundary_impulse_tracer, &
193  "If true, use the boundary impulse tracer.", &
194  default=.false.)
195 
196 #ifndef _USE_GENERIC_TRACER
197  if (cs%use_MOM_generic_tracer) call mom_error(fatal, &
198  "call_tracer_register: use_MOM_generic_tracer=.true. BUT not compiled")
199 #endif
200 
201 ! Add other user-provided calls to register tracers for restarting here. Each
202 ! tracer package registration call returns a logical false if it cannot be run
203 ! for some reason. This then overrides the run-time selection from above.
204  if (cs%use_USER_tracer_example) cs%use_USER_tracer_example = &
205  user_register_tracer_example(hi, gv, param_file, cs%USER_tracer_example_CSp, &
206  tr_reg, restart_cs)
207  if (cs%use_DOME_tracer) cs%use_DOME_tracer = &
208  register_dome_tracer(hi, gv, param_file, cs%DOME_tracer_CSp, &
209  tr_reg, restart_cs)
210  if (cs%use_ISOMIP_tracer) cs%use_ISOMIP_tracer = &
211  register_isomip_tracer(hi, gv, param_file, cs%ISOMIP_tracer_CSp, &
212  tr_reg, restart_cs)
213  if (cs%use_ideal_age) cs%use_ideal_age = &
214  register_ideal_age_tracer(hi, gv, param_file, cs%ideal_age_tracer_CSp, &
215  tr_reg, restart_cs)
216  if (cs%use_regional_dyes) cs%use_regional_dyes = &
217  register_dye_tracer(hi, gv, param_file, cs%dye_tracer_CSp, &
218  tr_reg, restart_cs)
219  if (cs%use_oil) cs%use_oil = &
220  register_oil_tracer(hi, gv, param_file, cs%oil_tracer_CSp, &
221  tr_reg, restart_cs)
222  if (cs%use_advection_test_tracer) cs%use_advection_test_tracer = &
223  register_advection_test_tracer(hi, gv, param_file, cs%advection_test_tracer_CSp, &
224  tr_reg, restart_cs)
225  if (cs%use_OCMIP2_CFC) cs%use_OCMIP2_CFC = &
226  register_ocmip2_cfc(hi, gv, param_file, cs%OCMIP2_CFC_CSp, &
227  tr_reg, restart_cs)
228 #ifdef _USE_GENERIC_TRACER
229  if (cs%use_MOM_generic_tracer) cs%use_MOM_generic_tracer = &
230  register_mom_generic_tracer(hi, gv, param_file, cs%MOM_generic_tracer_CSp, &
231  tr_reg, restart_cs)
232 #endif
233  if (cs%use_pseudo_salt_tracer) cs%use_pseudo_salt_tracer = &
234  register_pseudo_salt_tracer(hi, gv, param_file, cs%pseudo_salt_tracer_CSp, &
235  tr_reg, restart_cs)
236  if (cs%use_boundary_impulse_tracer) cs%use_boundary_impulse_tracer = &
237  register_boundary_impulse_tracer(hi, gv, param_file, cs%boundary_impulse_tracer_CSp, &
238  tr_reg, restart_cs)
239 
240 
241 end subroutine call_tracer_register
242 
243 !> This subroutine calls all registered tracer initialization
244 !! subroutines.
245 subroutine tracer_flow_control_init(restart, day, G, GV, h, param_file, diag, OBC, &
246  CS, sponge_CSp, ALE_sponge_CSp, diag_to_Z_CSp, tv)
247  logical, intent(in) :: restart !< 1 if the fields have already
248  !! been read from a restart file.
249  type(time_type), target, intent(in) :: day !< Time of the start of the run.
250  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
251  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid
252  !! structure.
253  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: h !< Layer thicknesses, in H
254  !! (usually m or kg m-2)
255  type(param_file_type), intent(in) :: param_file !< A structure to parse for
256  !! run-time parameters
257  type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to
258  !! regulate diagnostic output.
259  type(ocean_obc_type), pointer :: OBC !< This open boundary condition
260  !! type specifies whether, where,
261  !! and what open boundary
262  !! conditions are used.
263  type(tracer_flow_control_cs), pointer :: CS !< The control structure returned
264  !! by a previous call to
265  !! call_tracer_register.
266  type(sponge_cs), pointer :: sponge_CSp !< A pointer to the control
267  !! structure for the sponges, if they are in use.
268  !! Otherwise this may be unassociated.
269  type(ale_sponge_cs), pointer :: ALE_sponge_CSp !< A pointer to the control
270  !! structure for the ALE sponges, if they are in use.
271  !! Otherwise this may be unassociated.
272  type(diag_to_z_cs), pointer :: diag_to_Z_CSp !< A pointer to the control
273  !! structure for diagnostics in depth space.
274  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
275  !! thermodynamic variables
276 ! This subroutine calls all registered tracer initialization
277 ! subroutines.
278 
279 ! Arguments: restart - 1 if the fields have already been read from
280 ! a restart file.
281 ! (in) day - Time of the start of the run.
282 ! (in) G - The ocean's grid structure.
283 ! (in) GV - The ocean's vertical grid structure.
284 ! (in) h - Layer thickness, in m (Boussinesq) or kg m-2 (non-Boussinesq).
285 ! (in) diag - A structure that is used to regulate diagnostic output.
286 ! (in) OBC - This open boundary condition type specifies whether, where,
287 ! and what open boundary conditions are used.
288 ! (in) CS - The control structure returned by a previous call to
289 ! call_tracer_register.
290 ! (in/out) sponge_CSp - A pointer to the control structure for the sponges, if
291 ! they are in use. Otherwise this may be unassociated.
292 ! (in/out) ALE_sponge_CSp - A pointer to the control structure for the ALE sponges, if they are
293 ! in use. Otherwise this may be unassociated.
294 ! (in/out) diag_to_Z_Csp - A pointer to the control structure for diagnostics
295 ! in depth space.
296  if (.not. associated(cs)) call mom_error(fatal, "tracer_flow_control_init: "// &
297  "Module must be initialized via call_tracer_register before it is used.")
298 
299 ! Add other user-provided calls here.
300  if (cs%use_USER_tracer_example) &
301  call user_initialize_tracer(restart, day, g, gv, h, diag, obc, cs%USER_tracer_example_CSp, &
302  sponge_csp, diag_to_z_csp)
303  if (cs%use_DOME_tracer) &
304  call initialize_dome_tracer(restart, day, g, gv, h, diag, obc, cs%DOME_tracer_CSp, &
305  sponge_csp, diag_to_z_csp)
306  if (cs%use_ISOMIP_tracer) &
307  call initialize_isomip_tracer(restart, day, g, gv, h, diag, obc, cs%ISOMIP_tracer_CSp, &
308  ale_sponge_csp, diag_to_z_csp)
309  if (cs%use_ideal_age) &
310  call initialize_ideal_age_tracer(restart, day, g, gv, h, diag, obc, cs%ideal_age_tracer_CSp, &
311  sponge_csp, diag_to_z_csp)
312  if (cs%use_regional_dyes) &
313  call initialize_dye_tracer(restart, day, g, gv, h, diag, obc, cs%dye_tracer_CSp, &
314  sponge_csp, diag_to_z_csp)
315  if (cs%use_oil) &
316  call initialize_oil_tracer(restart, day, g, gv, h, diag, obc, cs%oil_tracer_CSp, &
317  sponge_csp, diag_to_z_csp)
318  if (cs%use_advection_test_tracer) &
319  call initialize_advection_test_tracer(restart, day, g, gv, h, diag, obc, cs%advection_test_tracer_CSp, &
320  sponge_csp, diag_to_z_csp)
321  if (cs%use_OCMIP2_CFC) &
322  call initialize_ocmip2_cfc(restart, day, g, gv, h, diag, obc, cs%OCMIP2_CFC_CSp, &
323  sponge_csp, diag_to_z_csp)
324 #ifdef _USE_GENERIC_TRACER
325  if (cs%use_MOM_generic_tracer) &
326  call initialize_mom_generic_tracer(restart, day, g, gv, h, param_file, diag, obc, &
327  cs%MOM_generic_tracer_CSp, sponge_csp, ale_sponge_csp, diag_to_z_csp)
328 #endif
329  if (cs%use_pseudo_salt_tracer) &
330  call initialize_pseudo_salt_tracer(restart, day, g, gv, h, diag, obc, cs%pseudo_salt_tracer_CSp, &
331  sponge_csp, diag_to_z_csp, tv)
332  if (cs%use_boundary_impulse_tracer) &
333  call initialize_boundary_impulse_tracer(restart, day, g, gv, h, diag, obc, cs%boundary_impulse_tracer_CSp, &
334  sponge_csp, diag_to_z_csp, tv)
335 
336 end subroutine tracer_flow_control_init
337 
338 ! #@# This subroutine needs a doxygen description
339 subroutine get_chl_from_model(Chl_array, G, CS)
340  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(out) :: Chl_array !< The array into which the
341  !! model's Chlorophyll-A
342  !! concentrations in mg m-3 are
343  !! to be read.
344  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
345  type(tracer_flow_control_cs), pointer :: CS !< The control structure returned
346  !! by a previous call to
347  !! call_tracer_register.
348 ! Arguments: Chl_array - The array into which the model's Chlorophyll-A
349 ! concentrations in mg m-3 are to be read.
350 ! (in) G - The ocean's grid structure.
351 ! (in) CS - The control structure returned by a previous call to
352 ! call_tracer_register.
353 
354 #ifdef _USE_GENERIC_TRACER
355  if (cs%use_MOM_generic_tracer) then
356  call mom_generic_tracer_get('chl','field',chl_array, cs%MOM_generic_tracer_CSp)
357  else
358  call mom_error(fatal, "get_chl_from_model was called in a configuration "// &
359  "that is unable to provide a sensible model-based value.\n"// &
360  "CS%use_MOM_generic_tracer is false and no other viable options are on.")
361  endif
362 #else
363  call mom_error(fatal, "get_chl_from_model was called in a configuration "// &
364  "that is unable to provide a sensible model-based value.\n"// &
365  "_USE_GENERIC_TRACER is undefined and no other options "//&
366  "are currently viable.")
367 #endif
368 
369 end subroutine get_chl_from_model
370 
371 !> This subroutine calls the individual tracer modules' subroutines to
372 !! specify or read quantities related to their surface forcing.
373 subroutine call_tracer_set_forcing(state, fluxes, day_start, day_interval, G, CS)
375  type(surface), intent(inout) :: state !< A structure containing fields that
376  !! describe the surface state of the
377  !! ocean.
378  type(forcing), intent(inout) :: fluxes !< A structure containing pointers to any
379  !! possible forcing fields. Unused fields
380  !! have NULL ptrs.
381  type(time_type), intent(in) :: day_start !< Start time of the fluxes.
382  type(time_type), intent(in) :: day_interval !< Length of time over which these
383  !! fluxes will be applied.
384  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
385  type(tracer_flow_control_cs), pointer :: CS !< The control structure returned by a
386  !! previous call to call_tracer_register.
387 
388 ! This subroutine calls the individual tracer modules' subroutines to
389 ! specify or read quantities related to their surface forcing.
390 ! Arguments: state - A structure containing fields that describe the
391 ! surface state of the ocean.
392 ! (out) fluxes - A structure containing pointers to any possible
393 ! forcing fields. Unused fields have NULL ptrs.
394 ! (in) day_start - Start time of the fluxes.
395 ! (in) day_interval - Length of time over which these fluxes
396 ! will be applied.
397 ! (in) G - The ocean's grid structure.
398 ! (in) CS - The control structure returned by a previous call to
399 ! call_tracer_register.
400 
401  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_set_forcing"// &
402  "Module must be initialized via call_tracer_register before it is used.")
403 ! if (CS%use_ideal_age) &
404 ! call ideal_age_tracer_set_forcing(state, fluxes, day_start, day_interval, &
405 ! G, CS%ideal_age_tracer_CSp)
406 
407 end subroutine call_tracer_set_forcing
408 
409 !> This subroutine calls all registered tracer column physics
410 !! subroutines.
411 subroutine call_tracer_column_fns(h_old, h_new, ea, eb, fluxes, Hml, dt, G, GV, tv, optics, CS, &
412  debug, evap_CFL_limit, minimum_forcing_depth)
413  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: h_old !< Layer thickness before entrainment,
414  !! in m (Boussinesq) or kg m-2
415  !! (non-Boussinesq).
416  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: h_new !< Layer thickness after entrainment,
417  !! in m or kg m-2.
418  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: ea !< an array to which the amount of
419  !! fluid entrained from the layer above during this call
420  !! will be added, in m or kg m-2, the same as h_old.
421  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: eb !< an array to which the amount of
422  !! fluid entrained from the layer below during this call
423  !! will be added, in m or kg m-2, the same as h_old.
424  type(forcing), intent(in) :: fluxes !< A structure containing pointers to
425  !! any possible forcing fields.
426  !! Unused fields have NULL ptrs.
427  real, dimension(NIMEM_,NJMEM_), intent(in) :: Hml !< Mixed layer depth (m)
428  real, intent(in) :: dt !< The amount of time covered by this
429  !! call, in s
430  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
431  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid
432  !! structure.
433  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
434  !! thermodynamic variables.
435  type(optics_type), pointer :: optics !< The structure containing optical
436  !! properties.
437  type(tracer_flow_control_cs), pointer :: CS !< The control structure returned by
438  !! a previous call to
439  !! call_tracer_register.
440  logical, intent(in) :: debug !< Calculates checksums
441  real, optional,intent(in) :: evap_CFL_limit !< Limits how much water
442  !! can be fluxed out of the top layer
443  !! Stored previously in diabatic] CS.
444  real, optional,intent(in) :: minimum_forcing_depth !< The smallest depth
445  !! over which fluxes can be applied
446  !! Stored previously in diabatic CS.
447 
448 ! This subroutine calls all registered tracer column physics
449 ! subroutines.
450 
451 ! Arguments: h_old - Layer thickness before entrainment, in m (Boussinesq)
452 ! or kg m-2 (non-Boussinesq).
453 ! (in) h_new - Layer thickness after entrainment, in m or kg m-2.
454 ! (in) ea - an array to which the amount of fluid entrained
455 ! from the layer above during this call will be
456 ! added, in m or kg m-2, the same as h_old.
457 ! (in) eb - an array to which the amount of fluid entrained
458 ! from the layer below during this call will be
459 ! added, in m or kg m-2, the same as h_old.
460 ! (in) fluxes - A structure containing pointers to any possible
461 ! forcing fields. Unused fields have NULL ptrs.
462 ! (in) dt - The amount of time covered by this call, in s.
463 ! (in) G - The ocean's grid structure.
464 ! (in) GV - The ocean's vertical grid structure.
465 ! (in) tv - The structure containing thermodynamic variables.
466 ! (in) optics - The structure containing optical properties.
467 ! (in) CS - The control structure returned by a previous call to
468 ! call_tracer_register.
469 ! (in) evap_CFL_limit - Limits how much water can be fluxed out of the top layer
470 ! Stored previously in diabatic CS.
471 ! (in) minimum_forcing_depth - The smallest depth over which fluxes can be applied
472 ! Stored previously in diabatic CS.
473 ! (in) debug - Calculates checksums
474 
475  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_column_fns: "// &
476  "Module must be initialized via call_tracer_register before it is used.")
477 
478  ! Use the applyTracerBoundaryFluxesInOut to handle surface fluxes
479  if (present(evap_cfl_limit) .and. present(minimum_forcing_depth)) then
480  ! Add calls to tracer column functions here.
481  if (cs%use_USER_tracer_example) &
482  call tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
483  g, gv, cs%USER_tracer_example_CSp)
484  if (cs%use_DOME_tracer) &
485  call dome_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
486  g, gv, cs%DOME_tracer_CSp, &
487  evap_cfl_limit=evap_cfl_limit, &
488  minimum_forcing_depth=minimum_forcing_depth)
489  if (cs%use_ISOMIP_tracer) &
490  call isomip_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
491  g, gv, cs%ISOMIP_tracer_CSp, &
492  evap_cfl_limit=evap_cfl_limit, &
493  minimum_forcing_depth=minimum_forcing_depth)
494  if (cs%use_ideal_age) &
495  call ideal_age_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
496  g, gv, cs%ideal_age_tracer_CSp, &
497  evap_cfl_limit=evap_cfl_limit, &
498  minimum_forcing_depth=minimum_forcing_depth)
499  if (cs%use_regional_dyes) &
500  call dye_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
501  g, gv, cs%dye_tracer_CSp, &
502  evap_cfl_limit=evap_cfl_limit, &
503  minimum_forcing_depth=minimum_forcing_depth)
504  if (cs%use_oil) &
505  call oil_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
506  g, gv, cs%oil_tracer_CSp, tv, &
507  evap_cfl_limit=evap_cfl_limit, &
508  minimum_forcing_depth=minimum_forcing_depth)
509 
510  if (cs%use_advection_test_tracer) &
511  call advection_test_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
512  g, gv, cs%advection_test_tracer_CSp, &
513  evap_cfl_limit=evap_cfl_limit, &
514  minimum_forcing_depth=minimum_forcing_depth)
515  if (cs%use_OCMIP2_CFC) &
516  call ocmip2_cfc_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
517  g, gv, cs%OCMIP2_CFC_CSp, &
518  evap_cfl_limit=evap_cfl_limit, &
519  minimum_forcing_depth=minimum_forcing_depth)
520 #ifdef _USE_GENERIC_TRACER
521  if (cs%use_MOM_generic_tracer) &
522  call mom_generic_tracer_column_physics(h_old, h_new, ea, eb, fluxes, hml, dt, &
523  g, gv, cs%MOM_generic_tracer_CSp, tv, optics, &
524  evap_cfl_limit=evap_cfl_limit, &
525  minimum_forcing_depth=minimum_forcing_depth)
526 #endif
527  if (cs%use_pseudo_salt_tracer) &
528  call pseudo_salt_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
529  g, gv, cs%pseudo_salt_tracer_CSp, tv, debug,&
530  evap_cfl_limit=evap_cfl_limit, &
531  minimum_forcing_depth=minimum_forcing_depth)
532  if (cs%use_boundary_impulse_tracer) &
533  call boundary_impulse_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
534  g, gv, cs%boundary_impulse_tracer_CSp, tv, debug,&
535  evap_cfl_limit=evap_cfl_limit, &
536  minimum_forcing_depth=minimum_forcing_depth)
537 
538 
539  else ! Apply tracer surface fluxes using ea on the first layer
540  if (cs%use_USER_tracer_example) &
541  call tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
542  g, gv, cs%USER_tracer_example_CSp)
543  if (cs%use_DOME_tracer) &
544  call dome_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
545  g, gv, cs%DOME_tracer_CSp)
546  if (cs%use_ISOMIP_tracer) &
547  call isomip_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
548  g, gv, cs%ISOMIP_tracer_CSp)
549  if (cs%use_ideal_age) &
550  call ideal_age_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
551  g, gv, cs%ideal_age_tracer_CSp)
552  if (cs%use_regional_dyes) &
553  call dye_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
554  g, gv, cs%dye_tracer_CSp)
555  if (cs%use_oil) &
556  call oil_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
557  g, gv, cs%oil_tracer_CSp, tv)
558  if (cs%use_advection_test_tracer) &
559  call advection_test_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
560  g, gv, cs%advection_test_tracer_CSp)
561  if (cs%use_OCMIP2_CFC) &
562  call ocmip2_cfc_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
563  g, gv, cs%OCMIP2_CFC_CSp)
564 #ifdef _USE_GENERIC_TRACER
565  if (cs%use_MOM_generic_tracer) &
566  call mom_generic_tracer_column_physics(h_old, h_new, ea, eb, fluxes, hml, dt, &
567  g, gv, cs%MOM_generic_tracer_CSp, tv, optics)
568 #endif
569  if (cs%use_pseudo_salt_tracer) &
570  call pseudo_salt_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
571  g, gv, cs%pseudo_salt_tracer_CSp, tv, debug)
572  if (cs%use_boundary_impulse_tracer) &
573  call boundary_impulse_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
574  g, gv, cs%boundary_impulse_tracer_CSp, tv, debug)
575 
576 
577  endif
578 
579 
580 end subroutine call_tracer_column_fns
581 
582 !> This subroutine calls all registered tracer packages to enable them to
583 !! add to the surface state returned to the coupler. These routines are optional.
584 subroutine call_tracer_stocks(h, stock_values, G, GV, CS, stock_names, stock_units, &
585  num_stocks, stock_index, got_min_max,global_min, global_max,xgmin, &
586  ygmin, zgmin, xgmax, ygmax, zgmax)
587  real, dimension(NIMEM_,NJMEM_,NKMEM_), &
588  intent(in) :: h !< Layer thicknesses, in H
589  !! (usually m or kg m-2).
590  real, dimension(:), intent(out) :: stock_values
591  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
592  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
593  type(tracer_flow_control_cs), pointer :: CS !< The control structure returned by a
594  !! previous call to
595  !! call_tracer_register.
596  character(len=*), dimension(:), optional, &
597  intent(out) :: stock_names !< Diagnostic names to use for each
598  !! stock.
599  character(len=*), dimension(:), optional, &
600  intent(out) :: stock_units !< Units to use in the metadata for
601  !! each stock.
602  integer, optional, &
603  intent(out) :: num_stocks !< The number of tracer stocks being
604  !! returned.
605  integer, optional, &
606  intent(in) :: stock_index !< The integer stock index from
607  !! stocks_constans_mod of the stock to be returned. If this is
608  !! present and greater than 0, only a single stock can be returned.
609  logical, dimension(:), optional, &
610  intent(inout) :: got_min_max
611  real, dimension(:), optional, &
612  intent(out) :: global_min, global_max
613  real, dimension(:), optional, &
614  intent(out) :: xgmin, ygmin, zgmin, xgmax, ygmax, zgmax
615 ! This subroutine calls all registered tracer packages to enable them to
616 ! add to the surface state returned to the coupler. These routines are optional.
617 
618 ! Arguments: h - Layer thickness, in m (Boussinesq) or kg m-2 (non-Boussinesq).
619 ! (out) stock_values - The integrated amounts of a tracer on the current
620 ! PE, usually in kg x concentration.
621 ! (in) G - The ocean's grid structure.
622 ! (in) GV - The ocean's vertical grid structure.
623 ! (in) CS - The control structure returned by a previous call to
624 ! call_tracer_register.
625 ! (out,opt) stock_names - Diagnostic names to use for each stock.
626 ! (out,opt) stock_units - Units to use in the metadata for each stock.
627 ! (out,opt) num_stocks - The number of tracer stocks being returned.
628 ! (in,opt) stock_index - The integer stock index from stocks_constans_mod of
629 ! the stock to be returned. If this is present and
630 ! greater than 0, only a single stock can be returned.
631  character(len=200), dimension(MAX_FIELDS_) :: names, units
632  character(len=200) :: set_pkg_name
633  real, dimension(MAX_FIELDS_) :: values
634  integer :: max_ns, ns_tot, ns, index, pkg, max_pkgs, nn
635 
636  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_stocks: "// &
637  "Module must be initialized via call_tracer_register before it is used.")
638 
639  index = -1 ; if (present(stock_index)) index = stock_index
640  ns_tot = 0
641  max_ns = size(stock_values)
642  if (present(stock_names)) max_ns = min(max_ns,size(stock_names))
643  if (present(stock_units)) max_ns = min(max_ns,size(stock_units))
644 
645 ! Add other user-provided calls here.
646  if (cs%use_USER_tracer_example) then
647  ns = user_tracer_stock(h, values, g, gv, cs%USER_tracer_example_CSp, &
648  names, units, stock_index)
649  call store_stocks("tracer_example", ns, names, units, values, index, stock_values, &
650  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
651  endif
652 ! if (CS%use_DOME_tracer) then
653 ! ns = DOME_tracer_stock(h, values, G, GV, CS%DOME_tracer_CSp, &
654 ! names, units, stock_index)
655 ! call store_stocks("DOME_tracer", ns, names, units, values, index, stock_values, &
656 ! set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
657 ! endif
658  if (cs%use_ideal_age) then
659  ns = ideal_age_stock(h, values, g, gv, cs%ideal_age_tracer_CSp, &
660  names, units, stock_index)
661  call store_stocks("ideal_age_example", ns, names, units, values, index, &
662  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
663  endif
664  if (cs%use_regional_dyes) then
665  ns = dye_stock(h, values, g, gv, cs%dye_tracer_CSp, &
666  names, units, stock_index)
667  call store_stocks("regional_dyes", ns, names, units, values, index, &
668  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
669  endif
670  if (cs%use_oil) then
671  ns = oil_stock(h, values, g, gv, cs%oil_tracer_CSp, &
672  names, units, stock_index)
673  call store_stocks("oil_tracer", ns, names, units, values, index, &
674  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
675  endif
676  if (cs%use_OCMIP2_CFC) then
677  ns = ocmip2_cfc_stock(h, values, g, gv, cs%OCMIP2_CFC_CSp, names, units, stock_index)
678  call store_stocks("MOM_OCMIP2_CFC", ns, names, units, values, index, stock_values, &
679  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
680  endif
681 
682  if (cs%use_advection_test_tracer) then
683  ns = advection_test_stock( h, values, g, gv, cs%advection_test_tracer_CSp, &
684  names, units, stock_index )
685  call store_stocks("advection_test_tracer", ns, names, units, values, index, &
686  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
687  endif
688 
689 #ifdef _USE_GENERIC_TRACER
690  if (cs%use_MOM_generic_tracer) then
691  ns = mom_generic_tracer_stock(h, values, g, gv, cs%MOM_generic_tracer_CSp, &
692  names, units, stock_index)
693  call store_stocks("MOM_generic_tracer", ns, names, units, values, index, stock_values, &
694  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
695  nn=ns_tot-ns+1
696  nn=mom_generic_tracer_min_max(nn, got_min_max, global_min, global_max, xgmin, ygmin, zgmin, xgmax, ygmax, zgmax ,&
697  g, cs%MOM_generic_tracer_CSp,names, units)
698 
699  endif
700 #endif
701  if (cs%use_pseudo_salt_tracer) then
702  ns = pseudo_salt_stock(h, values, g, gv, cs%pseudo_salt_tracer_CSp, &
703  names, units, stock_index)
704  call store_stocks("pseudo_salt_tracer", ns, names, units, values, index, &
705  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
706  endif
707 
708  if (cs%use_boundary_impulse_tracer) then
709  ns = boundary_impulse_stock(h, values, g, gv, cs%boundary_impulse_tracer_CSp, &
710  names, units, stock_index)
711  call store_stocks("boundary_impulse_tracer", ns, names, units, values, index, &
712  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
713  endif
714 
715  if (ns_tot == 0) stock_values(1) = 0.0
716 
717  if (present(num_stocks)) num_stocks = ns_tot
718 
719 end subroutine call_tracer_stocks
720 
721 !> This routine stores the stocks and does error handling for call_tracer_stocks.
722 subroutine store_stocks(pkg_name, ns, names, units, values, index, stock_values, &
723  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
724  character(len=*), intent(in) :: pkg_name
725  integer, intent(in) :: ns
726  character(len=*), dimension(:), intent(in) :: names, units
727  real, dimension(:), intent(in) :: values
728  integer, intent(in) :: index
729  real, dimension(:), intent(inout) :: stock_values
730  character(len=*), intent(inout) :: set_pkg_name
731  integer, intent(in) :: max_ns
732  integer, intent(inout) :: ns_tot
733  character(len=*), dimension(:), optional, intent(inout) :: stock_names, stock_units
734 
735 ! This routine stores the stocks and does error handling for call_tracer_stocks.
736  character(len=16) :: ind_text, ns_text, max_text
737  integer :: n
738 
739  if ((index > 0) .and. (ns > 0)) then
740  write(ind_text,'(i8)') index
741  if (ns > 1) then
742  call mom_error(fatal,"Tracer package "//trim(pkg_name)//&
743  " is not permitted to return more than one value when queried"//&
744  " for specific stock index "//trim(adjustl(ind_text))//".")
745  elseif (ns+ns_tot > 1) then
746  call mom_error(fatal,"Tracer packages "//trim(pkg_name)//" and "//&
747  trim(set_pkg_name)//" both attempted to set values for"//&
748  " specific stock index "//trim(adjustl(ind_text))//".")
749  else
750  set_pkg_name = pkg_name
751  endif
752  endif
753 
754  if (ns_tot+ns > max_ns) then
755  write(ns_text,'(i8)') ns_tot+ns ; write(max_text,'(i8)') max_ns
756  call mom_error(fatal,"Attempted to return more tracer stock values (at least "//&
757  trim(adjustl(ns_text))//") than the size "//trim(adjustl(max_text))//&
758  "of the smallest value, name, or units array.")
759  endif
760 
761  do n=1,ns
762  stock_values(ns_tot+n) = values(n)
763  if (present(stock_names)) stock_names(ns_tot+n) = names(n)
764  if (present(stock_units)) stock_units(ns_tot+n) = units(n)
765  enddo
766  ns_tot = ns_tot + ns
767 
768 end subroutine store_stocks
769 
770 !> This subroutine calls all registered tracer packages to enable them to
771 !! add to the surface state returned to the coupler. These routines are optional.
772 subroutine call_tracer_surface_state(state, h, G, CS)
773  type(surface), intent(inout) :: state !< A structure containing fields that
774  !! describe the surface state of the ocean.
775  real, dimension(NIMEM_,NJMEM_,NKMEM_), &
776  intent(in) :: h !< Layer thicknesses, in H
777  !! (usually m or kg m-2).
778  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
779  type(tracer_flow_control_cs), pointer :: CS !< The control structure returned by a
780  !! previous call to call_tracer_register.
781 ! This subroutine calls all registered tracer packages to enable them to
782 ! add to the surface state returned to the coupler. These routines are optional.
783 
784 ! Arguments: state - A structure containing fields that describe the
785 ! surface state of the ocean.
786 ! (in) h - Layer thickness, in m (Boussinesq) or kg m-2 (non-Boussinesq).
787 ! (in) G - The ocean's grid structure.
788 ! (in) CS - The control structure returned by a previous call to
789 ! call_tracer_register.
790 
791  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_surface_state: "// &
792  "Module must be initialized via call_tracer_register before it is used.")
793 
794 ! Add other user-provided calls here.
795  if (cs%use_USER_tracer_example) &
796  call user_tracer_surface_state(state, h, g, cs%USER_tracer_example_CSp)
797  if (cs%use_DOME_tracer) &
798  call dome_tracer_surface_state(state, h, g, cs%DOME_tracer_CSp)
799  if (cs%use_ISOMIP_tracer) &
800  call isomip_tracer_surface_state(state, h, g, cs%ISOMIP_tracer_CSp)
801  if (cs%use_ideal_age) &
802  call ideal_age_tracer_surface_state(state, h, g, cs%ideal_age_tracer_CSp)
803  if (cs%use_regional_dyes) &
804  call dye_tracer_surface_state(state, h, g, cs%dye_tracer_CSp)
805  if (cs%use_oil) &
806  call oil_tracer_surface_state(state, h, g, cs%oil_tracer_CSp)
807  if (cs%use_advection_test_tracer) &
808  call advection_test_tracer_surface_state(state, h, g, cs%advection_test_tracer_CSp)
809  if (cs%use_OCMIP2_CFC) &
810  call ocmip2_cfc_surface_state(state, h, g, cs%OCMIP2_CFC_CSp)
811 #ifdef _USE_GENERIC_TRACER
812  if (cs%use_MOM_generic_tracer) &
813  call mom_generic_tracer_surface_state(state, h, g, cs%MOM_generic_tracer_CSp)
814 #endif
815 
816 end subroutine call_tracer_surface_state
817 
818 subroutine tracer_flow_control_end(CS)
819  type(tracer_flow_control_cs), pointer :: CS
820 
821  if (cs%use_USER_tracer_example) &
822  call user_tracer_example_end(cs%USER_tracer_example_CSp)
823  if (cs%use_DOME_tracer) call dome_tracer_end(cs%DOME_tracer_CSp)
824  if (cs%use_ISOMIP_tracer) call isomip_tracer_end(cs%ISOMIP_tracer_CSp)
825  if (cs%use_ideal_age) call ideal_age_example_end(cs%ideal_age_tracer_CSp)
826  if (cs%use_regional_dyes) call regional_dyes_end(cs%dye_tracer_CSp)
827  if (cs%use_oil) call oil_tracer_end(cs%oil_tracer_CSp)
828  if (cs%use_advection_test_tracer) call advection_test_tracer_end(cs%advection_test_tracer_CSp)
829  if (cs%use_OCMIP2_CFC) call ocmip2_cfc_end(cs%OCMIP2_CFC_CSp)
830 #ifdef _USE_GENERIC_TRACER
831  if (cs%use_MOM_generic_tracer) call end_mom_generic_tracer(cs%MOM_generic_tracer_CSp)
832 #endif
833  if (cs%use_pseudo_salt_tracer) call pseudo_salt_tracer_end(cs%pseudo_salt_tracer_CSp)
834  if (cs%use_boundary_impulse_tracer) call boundary_impulse_tracer_end(cs%boundary_impulse_tracer_CSp)
835 
836  if (associated(cs)) deallocate(cs)
837 end subroutine tracer_flow_control_end
838 
839 end module mom_tracer_flow_control
subroutine store_stocks(pkg_name, ns, names, units, values, index, stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
This routine stores the stocks and does error handling for call_tracer_stocks.
integer function, public pseudo_salt_stock(h, stocks, G, GV, CS, names, units, stock_index)
logical function, public register_boundary_impulse_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
Read in runtime options and add boundary impulse tracer to tracer registry.
The following structure contains pointers to various fields which may be used describe the surface st...
subroutine, public ideal_age_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
subroutine, public advection_test_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
logical function, public register_dye_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
subroutine, public regional_dyes_end(CS)
subroutine, public oil_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, tv, evap_CFL_limit, minimum_forcing_depth)
Definition: oil_tracer.F90:425
subroutine, public ideal_age_tracer_surface_state(state, h, G, CS)
subroutine, public pseudo_salt_tracer_end(CS)
This module implements boundary forcing for MOM6.
subroutine, public initialize_ideal_age_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
subroutine, public user_initialize_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
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...
subroutine, public boundary_impulse_tracer_end(CS)
subroutine, public ideal_age_example_end(CS)
subroutine, public tracer_flow_control_init(restart, day, G, GV, h, param_file, diag, OBC, CS, sponge_CSp, ALE_sponge_CSp, diag_to_Z_CSp, tv)
This subroutine calls all registered tracer initialization subroutines.
Provides the ocean grid type.
Definition: MOM_grid.F90:2
integer function, public advection_test_stock(h, stocks, G, GV, CS, names, units, stock_index)
subroutine, public isomip_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
This subroutine applies diapycnal diffusion and any other column.
integer function, public dye_stock(h, stocks, G, GV, CS, names, units, stock_index)
subroutine, public dome_tracer_surface_state(state, h, G, CS)
subroutine, public call_tracer_column_fns(h_old, h_new, ea, eb, fluxes, Hml, dt, G, GV, tv, optics, CS, debug, evap_CFL_limit, minimum_forcing_depth)
This subroutine calls all registered tracer column physics subroutines.
subroutine, public pseudo_salt_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, tv, debug, evap_CFL_limit, minimum_forcing_depth)
This module contains the routines used to set up and use a set of (one for now) dynamically passive t...
subroutine, public call_tracer_register(HI, GV, param_file, CS, tr_Reg, restart_CS)
The following 5 subroutines and associated definitions provide the machinery to register and call the...
Defines the horizontal index type (hor_index_type) used for providing index ranges.
integer function, public user_tracer_stock(h, stocks, G, GV, CS, names, units, stock_index)
logical function, public register_ocmip2_cfc(HI, GV, param_file, CS, tr_Reg, restart_CS)
This module contains the routines used to apply sponge layers when using the ALE mode. Applying sponges requires the following: (1) initialize_ALE_sponge (2) set_up_ALE_sponge_field (tracers) and set_up_ALE_sponge_vel_field (vel) (3) apply_ALE_sponge (4) init_ALE_sponge_diags (not being used for now) (5) ALE_sponge_end (not being used for now)
subroutine, public initialize_oil_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
Definition: oil_tracer.F90:279
SPONGE control structure.
Container for horizontal index ranges for data, computational and global domains. ...
subroutine, public initialize_pseudo_salt_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp, tv)
subroutine, public user_tracer_surface_state(state, h, G, CS)
subroutine, public initialize_isomip_tracer(restart, day, G, GV, h, diag, OBC, CS, ALE_sponge_CSp, diag_to_Z_CSp)
Initializes the NTR tracer fields in tr(:,:,:,:)
integer function, public boundary_impulse_stock(h, stocks, G, GV, CS, names, units, stock_index)
Calculate total inventory of tracer.
Implements a boundary impulse response tracer to calculate Green&#39;s functions.
subroutine, public tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS)
subroutine, public oil_tracer_surface_state(state, h, G, CS)
Definition: oil_tracer.F90:617
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
subroutine, public call_tracer_surface_state(state, h, G, CS)
This subroutine calls all registered tracer packages to enable them to add to the surface state retur...
subroutine, public call_tracer_stocks(h, stock_values, G, GV, CS, stock_names, stock_units, num_stocks, stock_index, got_min_max, global_min, global_max, xgmin, ygmin, zgmin, xgmax, ygmax, zgmax)
This subroutine calls all registered tracer packages to enable them to add to the surface state retur...
subroutine, public user_tracer_example_end(CS)
subroutine, public dome_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
subroutine, public pseudo_salt_tracer_surface_state(state, h, G, CS)
subroutine, public oil_tracer_end(CS)
Definition: oil_tracer.F90:646
Type to carry basic tracer information.
subroutine, public call_tracer_set_forcing(state, fluxes, day_start, day_interval, G, CS)
This subroutine calls the individual tracer modules&#39; subroutines to specify or read quantities relate...
subroutine, public tracer_flow_control_end(CS)
subroutine, public boundary_impulse_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, tv, debug, evap_CFL_limit, minimum_forcing_depth)
integer function, public oil_stock(h, stocks, G, GV, CS, names, units, stock_index)
Definition: oil_tracer.F90:563
logical function, public register_isomip_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
This subroutine is used to register tracer fields.
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
subroutine, public initialize_boundary_impulse_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp, tv)
Initialize tracer from restart or set to 1 at surface to initialize.
logical function, public user_register_tracer_example(HI, GV, param_file, CS, tr_Reg, restart_CS)
subroutine, public isomip_tracer_end(CS)
logical function, public register_ideal_age_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
logical function, public register_oil_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
Definition: oil_tracer.F90:147
logical function, public register_advection_test_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
subroutine, public initialize_dome_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
logical function, public register_dome_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
subroutine, public advection_test_tracer_end(CS)
subroutine, public initialize_dye_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
subroutine, public get_chl_from_model(Chl_array, G, CS)
integer function, public ocmip2_cfc_stock(h, stocks, G, GV, CS, names, units, stock_index)
This function calculates the mass-weighted integral of all tracer stocks, returning the number of sto...
subroutine, public ocmip2_cfc_end(CS)
subroutine, public ocmip2_cfc_surface_state(state, h, G, CS)
subroutine, public initialize_advection_test_tracer(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
Controls where open boundary conditions are applied.
subroutine, public ocmip2_cfc_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
This subroutine applies diapycnal diffusion and any other column.
subroutine, public advection_test_tracer_surface_state(state, h, G, CS)
subroutine, public dye_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
subroutine, public dome_tracer_end(CS)
subroutine, public boundary_impulse_tracer_surface_state(state, h, G, CS)
Called if returned if coupler needs to know about tracer, currently unused.
tracer control structure
subroutine, public initialize_ocmip2_cfc(restart, day, G, GV, h, diag, OBC, CS, sponge_CSp, diag_to_Z_CSp)
This subroutine initializes the NTR tracer fields in tr(:,:,:,:) and it sets up the tracer output...
subroutine, public mom_error(level, message, all_print)
logical function, public register_pseudo_salt_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
subroutine, public dye_tracer_surface_state(state, h, G, CS)
integer function, public ideal_age_stock(h, stocks, G, GV, CS, names, units, stock_index)
subroutine, public isomip_tracer_surface_state(state, h, G, CS)
This particular tracer package does not report anything back to the coupler.