MOM6
mom_tracer_flow_control Module Reference

Detailed Description

Orchestrates the registration and calling of tracer packages.

Data Types

type  tracer_flow_control_cs
 The control structure for orchestrating the calling of tracer packages. More...
 

Functions/Subroutines

subroutine, public call_tracer_flux_init (verbosity)
 This subroutine carries out a series of calls to initialize the air-sea tracer fluxes, but it does not record the generated indicies, and it may be called before the ocean model has been initialized and may be called on non-ocean PEs. It is not necessary to call this routine for ocean-only runs, because the same calls are made again inside of the routines called by call_tracer_register. More...
 
subroutine, public call_tracer_register (HI, GV, US, param_file, CS, tr_Reg, restart_CS)
 The following 5 subroutines and associated definitions provide the machinery to register and call the subroutines that initialize tracers and apply vertical column processes to tracers. More...
 
subroutine, public tracer_flow_control_init (restart, day, G, GV, US, h, param_file, diag, OBC, CS, sponge_CSp, ALE_sponge_CSp, tv)
 This subroutine calls all registered tracer initialization subroutines. More...
 
subroutine, public get_chl_from_model (Chl_array, G, CS)
 This subroutine extracts the chlorophyll concentrations from the model state, if possible. More...
 
subroutine, public call_tracer_set_forcing (state, fluxes, day_start, day_interval, G, CS)
 This subroutine calls the individual tracer modules' subroutines to specify or read quantities related to their surface forcing. More...
 
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. More...
 
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 returned to the coupler. These routines are optional. More...
 
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. More...
 
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 returned to the coupler. These routines are optional. More...
 
subroutine, public tracer_flow_control_end (CS)
 

Function/Subroutine Documentation

◆ call_tracer_column_fns()

subroutine, public mom_tracer_flow_control::call_tracer_column_fns ( real, dimension( : , : , : ), intent(in)  h_old,
real, dimension( : , : , : ), intent(in)  h_new,
real, dimension( : , : , : ), intent(in)  ea,
real, dimension( : , : , : ), intent(in)  eb,
type(forcing), intent(in)  fluxes,
real, dimension( : , : ), intent(in)  Hml,
real, intent(in)  dt,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(thermo_var_ptrs), intent(in)  tv,
type(optics_type), pointer  optics,
type(tracer_flow_control_cs), pointer  CS,
logical, intent(in)  debug,
real, intent(in), optional  evap_CFL_limit,
real, intent(in), optional  minimum_forcing_depth 
)

This subroutine calls all registered tracer column physics subroutines.

Parameters
[in]h_oldLayer thickness before entrainment [H ~> m or kg m-2].
[in]h_newLayer thickness after entrainment [H ~> m or kg m-2].
[in]eaan array to which the amount of fluid entrained from the layer above during this call will be added [H ~> m or kg m-2].
[in]eban array to which the amount of fluid entrained from the layer below during this call will be added [H ~> m or kg m-2].
[in]fluxesA structure containing pointers to any possible forcing fields. Unused fields have NULL ptrs.
[in]hmlMixed layer depth [H ~> m or kg m-2]
[in]dtThe amount of time covered by this call [s]
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
[in]tvA structure pointing to various thermodynamic variables.
opticsThe structure containing optical properties.
csThe control structure returned by a previous call to call_tracer_register.
[in]debugIf true calculate checksums
[in]evap_cfl_limitLimit on the fraction of the water that can be fluxed out of the top layer in a timestep [nondim]
[in]minimum_forcing_depthThe smallest depth over which fluxes can be applied [H ~> m or kg m-2]

Definition at line 413 of file MOM_tracer_flow_control.F90.

413  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: h_old !< Layer thickness before entrainment
414  !! [H ~> m or kg m-2].
415  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: h_new !< Layer thickness after entrainment
416  !! [H ~> m or kg m-2].
417  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: ea !< an array to which the amount of
418  !! fluid entrained from the layer above during this call
419  !! will be added [H ~> m or kg m-2].
420  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: eb !< an array to which the amount of
421  !! fluid entrained from the layer below during this call
422  !! will be added [H ~> m or kg m-2].
423  type(forcing), intent(in) :: fluxes !< A structure containing pointers to
424  !! any possible forcing fields.
425  !! Unused fields have NULL ptrs.
426  real, dimension(NIMEM_,NJMEM_), intent(in) :: Hml !< Mixed layer depth [H ~> m or kg m-2]
427  real, intent(in) :: dt !< The amount of time covered by this
428  !! call [s]
429  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
430  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid
431  !! structure.
432  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
433  !! thermodynamic variables.
434  type(optics_type), pointer :: optics !< The structure containing optical
435  !! properties.
436  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned by
437  !! a previous call to
438  !! call_tracer_register.
439  logical, intent(in) :: debug !< If true calculate checksums
440  real, optional, intent(in) :: evap_CFL_limit !< Limit on the fraction of
441  !! the water that can be fluxed out
442  !! of the top layer in a timestep [nondim]
443  real, optional, intent(in) :: minimum_forcing_depth !< The smallest depth over
444  !! which fluxes can be applied [H ~> m or kg m-2]
445 
446  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_column_fns: "// &
447  "Module must be initialized via call_tracer_register before it is used.")
448 
449  ! Use the applyTracerBoundaryFluxesInOut to handle surface fluxes
450  if (present(evap_cfl_limit) .and. present(minimum_forcing_depth)) then
451  ! Add calls to tracer column functions here.
452  if (cs%use_USER_tracer_example) &
453  call tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
454  g, gv, cs%USER_tracer_example_CSp)
455  if (cs%use_DOME_tracer) &
456  call dome_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
457  g, gv, cs%DOME_tracer_CSp, &
458  evap_cfl_limit=evap_cfl_limit, &
459  minimum_forcing_depth=minimum_forcing_depth)
460  if (cs%use_ISOMIP_tracer) &
461  call isomip_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
462  g, gv, cs%ISOMIP_tracer_CSp, &
463  evap_cfl_limit=evap_cfl_limit, &
464  minimum_forcing_depth=minimum_forcing_depth)
465  if (cs%use_RGC_tracer) &
466  call rgc_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
467  g, gv, cs%RGC_tracer_CSp, &
468  evap_cfl_limit=evap_cfl_limit, &
469  minimum_forcing_depth=minimum_forcing_depth)
470  if (cs%use_ideal_age) &
471  call ideal_age_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
472  g, gv, cs%ideal_age_tracer_CSp, &
473  evap_cfl_limit=evap_cfl_limit, &
474  minimum_forcing_depth=minimum_forcing_depth)
475  if (cs%use_regional_dyes) &
476  call dye_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
477  g, gv, cs%dye_tracer_CSp, &
478  evap_cfl_limit=evap_cfl_limit, &
479  minimum_forcing_depth=minimum_forcing_depth)
480  if (cs%use_oil) &
481  call oil_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
482  g, gv, cs%oil_tracer_CSp, tv, &
483  evap_cfl_limit=evap_cfl_limit, &
484  minimum_forcing_depth=minimum_forcing_depth)
485 
486  if (cs%use_advection_test_tracer) &
487  call advection_test_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
488  g, gv, cs%advection_test_tracer_CSp, &
489  evap_cfl_limit=evap_cfl_limit, &
490  minimum_forcing_depth=minimum_forcing_depth)
491  if (cs%use_OCMIP2_CFC) &
492  call ocmip2_cfc_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
493  g, gv, cs%OCMIP2_CFC_CSp, &
494  evap_cfl_limit=evap_cfl_limit, &
495  minimum_forcing_depth=minimum_forcing_depth)
496 #ifdef _USE_GENERIC_TRACER
497  if (cs%use_MOM_generic_tracer) &
498  call mom_generic_tracer_column_physics(h_old, h_new, ea, eb, fluxes, hml, dt, &
499  g, gv, cs%MOM_generic_tracer_CSp, tv, optics, &
500  evap_cfl_limit=evap_cfl_limit, &
501  minimum_forcing_depth=minimum_forcing_depth)
502 #endif
503  if (cs%use_pseudo_salt_tracer) &
504  call pseudo_salt_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
505  g, gv, cs%pseudo_salt_tracer_CSp, tv, debug,&
506  evap_cfl_limit=evap_cfl_limit, &
507  minimum_forcing_depth=minimum_forcing_depth)
508  if (cs%use_boundary_impulse_tracer) &
509  call boundary_impulse_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
510  g, gv, cs%boundary_impulse_tracer_CSp, tv, debug,&
511  evap_cfl_limit=evap_cfl_limit, &
512  minimum_forcing_depth=minimum_forcing_depth)
513  if (cs%use_dyed_obc_tracer) &
514  call dyed_obc_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
515  g, gv, cs%dyed_obc_tracer_CSp, &
516  evap_cfl_limit=evap_cfl_limit, &
517  minimum_forcing_depth=minimum_forcing_depth)
518 
519 
520  else ! Apply tracer surface fluxes using ea on the first layer
521  if (cs%use_USER_tracer_example) &
522  call tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
523  g, gv, cs%USER_tracer_example_CSp)
524  if (cs%use_DOME_tracer) &
525  call dome_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
526  g, gv, cs%DOME_tracer_CSp)
527  if (cs%use_ISOMIP_tracer) &
528  call isomip_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
529  g, gv, cs%ISOMIP_tracer_CSp)
530  if (cs%use_RGC_tracer) &
531  call rgc_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
532  g, gv, cs%RGC_tracer_CSp)
533  if (cs%use_ideal_age) &
534  call ideal_age_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
535  g, gv, cs%ideal_age_tracer_CSp)
536  if (cs%use_regional_dyes) &
537  call dye_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
538  g, gv, cs%dye_tracer_CSp)
539  if (cs%use_oil) &
540  call oil_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
541  g, gv, cs%oil_tracer_CSp, tv)
542  if (cs%use_advection_test_tracer) &
543  call advection_test_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
544  g, gv, cs%advection_test_tracer_CSp)
545  if (cs%use_OCMIP2_CFC) &
546  call ocmip2_cfc_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
547  g, gv, cs%OCMIP2_CFC_CSp)
548 #ifdef _USE_GENERIC_TRACER
549  if (cs%use_MOM_generic_tracer) &
550  call mom_generic_tracer_column_physics(h_old, h_new, ea, eb, fluxes, hml, dt, &
551  g, gv, cs%MOM_generic_tracer_CSp, tv, optics)
552 #endif
553  if (cs%use_pseudo_salt_tracer) &
554  call pseudo_salt_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
555  g, gv, cs%pseudo_salt_tracer_CSp, tv, debug)
556  if (cs%use_boundary_impulse_tracer) &
557  call boundary_impulse_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
558  g, gv, cs%boundary_impulse_tracer_CSp, tv, debug)
559  if (cs%use_dyed_obc_tracer) &
560  call dyed_obc_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, &
561  g, gv, cs%dyed_obc_tracer_CSp)
562 
563 
564  endif
565 
566 

◆ call_tracer_flux_init()

subroutine, public mom_tracer_flow_control::call_tracer_flux_init ( integer, intent(in), optional  verbosity)

This subroutine carries out a series of calls to initialize the air-sea tracer fluxes, but it does not record the generated indicies, and it may be called before the ocean model has been initialized and may be called on non-ocean PEs. It is not necessary to call this routine for ocean-only runs, because the same calls are made again inside of the routines called by call_tracer_register.

Parameters
[in]verbosityA 0-9 integer indicating a level of verbosity.

Definition at line 117 of file MOM_tracer_flow_control.F90.

117  integer, optional, intent(in) :: verbosity !< A 0-9 integer indicating a level of verbosity.
118 
119  type(param_file_type) :: param_file ! A structure to parse for run-time parameters
120  character(len=40) :: mdl = "call_tracer_flux_init" ! This module's name.
121  logical :: use_OCMIP_CFCs, use_MOM_generic_tracer
122 
123  ! Determine which tracer routines with tracer fluxes are to be called. Note
124  ! that not every tracer package is required to have a flux_init call.
125  call get_mom_input(param_file, check_params=.false.)
126 
127  call get_param(param_file, mdl, "USE_OCMIP2_CFC", use_ocmip_cfcs, &
128  default=.false., do_not_log=.true.)
129  call get_param(param_file, mdl, "USE_generic_tracer", use_mom_generic_tracer,&
130  default=.false., do_not_log=.true.)
131  call close_param_file(param_file, quiet_close=.true.)
132 
133  if (use_ocmip_cfcs) call flux_init_ocmip2_cfc(verbosity=verbosity)
134  if (use_mom_generic_tracer) then
135 #ifdef _USE_GENERIC_TRACER
136  call mom_generic_flux_init(verbosity=verbosity)
137 #else
138  call mom_error(fatal, &
139  "call_tracer_flux_init: use_MOM_generic_tracer=.true. but MOM6 was "//&
140  "not compiled with _USE_GENERIC_TRACER")
141 #endif
142  endif
143 

◆ call_tracer_register()

subroutine, public mom_tracer_flow_control::call_tracer_register ( type(hor_index_type), intent(in)  HI,
type(verticalgrid_type), intent(in)  GV,
type(unit_scale_type), intent(in)  US,
type(param_file_type), intent(in)  param_file,
type(tracer_flow_control_cs), pointer  CS,
type(tracer_registry_type), pointer  tr_Reg,
type(mom_restart_cs), pointer  restart_CS 
)

The following 5 subroutines and associated definitions provide the machinery to register and call the subroutines that initialize tracers and apply vertical column processes to tracers.

Parameters
[in]hiA horizontal index type structure.
[in]gvThe ocean's vertical grid structure.
[in]usA dimensional unit scaling type
[in]param_fileA structure to parse for run-time parameters.
csA pointer that is set to point to the control structure for this module.
tr_regA pointer that is set to point to the control structure for the tracer advection and diffusion module.
restart_csA pointer to the restart control structure.

Definition at line 150 of file MOM_tracer_flow_control.F90.

150  type(hor_index_type), intent(in) :: HI !< A horizontal index type structure.
151  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
152  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
153  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time
154  !! parameters.
155  type(tracer_flow_control_CS), pointer :: CS !< A pointer that is set to point to the
156  !! control structure for this module.
157  type(tracer_registry_type), pointer :: tr_Reg !< A pointer that is set to point to the
158  !! control structure for the tracer
159  !! advection and diffusion module.
160  type(MOM_restart_CS), pointer :: restart_CS !< A pointer to the restart control
161  !! structure.
162 ! Arguments: HI - A horizontal index type structure.
163 ! (in) GV - The ocean's vertical grid structure.
164 ! (in) param_file - A structure indicating the open file to parse for
165 ! model parameter values.
166 ! (in/out) CS - A pointer that is set to point to the control structure
167 ! for this module
168 ! (in/out) tr_Reg - A pointer that is set to point to the control structure
169 ! for the tracer advection and diffusion module.
170 ! (in) restart_CS - A pointer to the restart control structure.
171 
172 ! This include declares and sets the variable "version".
173 #include "version_variable.h"
174  character(len=40) :: mdl = "MOM_tracer_flow_control" ! This module's name.
175 
176  if (associated(cs)) then
177  call mom_error(warning, "call_tracer_register called with an associated "// &
178  "control structure.")
179  return
180  else ; allocate(cs) ; endif
181 
182  ! Read all relevant parameters and write them to the model log.
183  call log_version(param_file, mdl, version, "")
184  call get_param(param_file, mdl, "USE_USER_TRACER_EXAMPLE", &
185  cs%use_USER_tracer_example, &
186  "If true, use the USER_tracer_example tracer package.", &
187  default=.false.)
188  call get_param(param_file, mdl, "USE_DOME_TRACER", cs%use_DOME_tracer, &
189  "If true, use the DOME_tracer tracer package.", &
190  default=.false.)
191  call get_param(param_file, mdl, "USE_ISOMIP_TRACER", cs%use_ISOMIP_tracer, &
192  "If true, use the ISOMIP_tracer tracer package.", &
193  default=.false.)
194  call get_param(param_file, mdl, "USE_RGC_TRACER", cs%use_RGC_tracer, &
195  "If true, use the RGC_tracer tracer package.", &
196  default=.false.)
197  call get_param(param_file, mdl, "USE_IDEAL_AGE_TRACER", cs%use_ideal_age, &
198  "If true, use the ideal_age_example tracer package.", &
199  default=.false.)
200  call get_param(param_file, mdl, "USE_REGIONAL_DYES", cs%use_regional_dyes, &
201  "If true, use the regional_dyes tracer package.", &
202  default=.false.)
203  call get_param(param_file, mdl, "USE_OIL_TRACER", cs%use_oil, &
204  "If true, use the oil_tracer tracer package.", &
205  default=.false.)
206  call get_param(param_file, mdl, "USE_ADVECTION_TEST_TRACER", cs%use_advection_test_tracer, &
207  "If true, use the advection_test_tracer tracer package.", &
208  default=.false.)
209  call get_param(param_file, mdl, "USE_OCMIP2_CFC", cs%use_OCMIP2_CFC, &
210  "If true, use the MOM_OCMIP2_CFC tracer package.", &
211  default=.false.)
212  call get_param(param_file, mdl, "USE_generic_tracer", cs%use_MOM_generic_tracer, &
213  "If true and _USE_GENERIC_TRACER is defined as a "//&
214  "preprocessor macro, use the MOM_generic_tracer packages.", &
215  default=.false.)
216  call get_param(param_file, mdl, "USE_PSEUDO_SALT_TRACER", cs%use_pseudo_salt_tracer, &
217  "If true, use the pseudo salt tracer, typically run as a diagnostic.", &
218  default=.false.)
219  call get_param(param_file, mdl, "USE_BOUNDARY_IMPULSE_TRACER", cs%use_boundary_impulse_tracer, &
220  "If true, use the boundary impulse tracer.", &
221  default=.false.)
222  call get_param(param_file, mdl, "USE_DYED_OBC_TRACER", cs%use_dyed_obc_tracer, &
223  "If true, use the dyed_obc_tracer tracer package.", &
224  default=.false.)
225 
226 #ifndef _USE_GENERIC_TRACER
227  if (cs%use_MOM_generic_tracer) call mom_error(fatal, &
228  "call_tracer_register: use_MOM_generic_tracer=.true. but MOM6 was "//&
229  "not compiled with _USE_GENERIC_TRACER")
230 #endif
231 
232 ! Add other user-provided calls to register tracers for restarting here. Each
233 ! tracer package registration call returns a logical false if it cannot be run
234 ! for some reason. This then overrides the run-time selection from above.
235  if (cs%use_USER_tracer_example) cs%use_USER_tracer_example = &
236  user_register_tracer_example(hi, gv, param_file, cs%USER_tracer_example_CSp, &
237  tr_reg, restart_cs)
238  if (cs%use_DOME_tracer) cs%use_DOME_tracer = &
239  register_dome_tracer(hi, gv, param_file, cs%DOME_tracer_CSp, &
240  tr_reg, restart_cs)
241  if (cs%use_ISOMIP_tracer) cs%use_ISOMIP_tracer = &
242  register_isomip_tracer(hi, gv, param_file, cs%ISOMIP_tracer_CSp, &
243  tr_reg, restart_cs)
244  if (cs%use_RGC_tracer) cs%use_RGC_tracer = &
245  register_rgc_tracer(hi, gv, param_file, cs%RGC_tracer_CSp, &
246  tr_reg, restart_cs)
247  if (cs%use_ideal_age) cs%use_ideal_age = &
248  register_ideal_age_tracer(hi, gv, param_file, cs%ideal_age_tracer_CSp, &
249  tr_reg, restart_cs)
250  if (cs%use_regional_dyes) cs%use_regional_dyes = &
251  register_dye_tracer(hi, gv, us, param_file, cs%dye_tracer_CSp, &
252  tr_reg, restart_cs)
253  if (cs%use_oil) cs%use_oil = &
254  register_oil_tracer(hi, gv, param_file, cs%oil_tracer_CSp, &
255  tr_reg, restart_cs)
256  if (cs%use_advection_test_tracer) cs%use_advection_test_tracer = &
257  register_advection_test_tracer(hi, gv, param_file, cs%advection_test_tracer_CSp, &
258  tr_reg, restart_cs)
259  if (cs%use_OCMIP2_CFC) cs%use_OCMIP2_CFC = &
260  register_ocmip2_cfc(hi, gv, param_file, cs%OCMIP2_CFC_CSp, &
261  tr_reg, restart_cs)
262 #ifdef _USE_GENERIC_TRACER
263  if (cs%use_MOM_generic_tracer) cs%use_MOM_generic_tracer = &
264  register_mom_generic_tracer(hi, gv, param_file, cs%MOM_generic_tracer_CSp, &
265  tr_reg, restart_cs)
266 #endif
267  if (cs%use_pseudo_salt_tracer) cs%use_pseudo_salt_tracer = &
268  register_pseudo_salt_tracer(hi, gv, param_file, cs%pseudo_salt_tracer_CSp, &
269  tr_reg, restart_cs)
270  if (cs%use_boundary_impulse_tracer) cs%use_boundary_impulse_tracer = &
271  register_boundary_impulse_tracer(hi, gv, param_file, cs%boundary_impulse_tracer_CSp, &
272  tr_reg, restart_cs)
273  if (cs%use_dyed_obc_tracer) cs%use_dyed_obc_tracer = &
274  register_dyed_obc_tracer(hi, gv, param_file, cs%dyed_obc_tracer_CSp, &
275  tr_reg, restart_cs)
276 
277 

◆ call_tracer_set_forcing()

subroutine, public mom_tracer_flow_control::call_tracer_set_forcing ( type(surface), intent(inout)  state,
type(forcing), intent(inout)  fluxes,
type(time_type), intent(in)  day_start,
type(time_type), intent(in)  day_interval,
type(ocean_grid_type), intent(in)  G,
type(tracer_flow_control_cs), pointer  CS 
)

This subroutine calls the individual tracer modules' subroutines to specify or read quantities related to their surface forcing.

Parameters
[in,out]stateA structure containing fields that describe the surface state of the ocean.
[in,out]fluxesA structure containing pointers to any possible forcing fields. Unused fields have NULL ptrs.
[in]day_startStart time of the fluxes.
[in]day_intervalLength of time over which these fluxes will be applied.
[in]gThe ocean's grid structure.
csThe control structure returned by a previous call to call_tracer_register.

Definition at line 388 of file MOM_tracer_flow_control.F90.

388 
389  type(surface), intent(inout) :: state !< A structure containing fields that
390  !! describe the surface state of the
391  !! ocean.
392  type(forcing), intent(inout) :: fluxes !< A structure containing pointers to any
393  !! possible forcing fields. Unused fields
394  !! have NULL ptrs.
395  type(time_type), intent(in) :: day_start !< Start time of the fluxes.
396  type(time_type), intent(in) :: day_interval !< Length of time over which these
397  !! fluxes will be applied.
398  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
399  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned by a
400  !! previous call to call_tracer_register.
401 
402  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_set_forcing"// &
403  "Module must be initialized via call_tracer_register before it is used.")
404 ! if (CS%use_ideal_age) &
405 ! call ideal_age_tracer_set_forcing(state, fluxes, day_start, day_interval, &
406 ! G, CS%ideal_age_tracer_CSp)
407 

◆ call_tracer_stocks()

subroutine, public mom_tracer_flow_control::call_tracer_stocks ( real, dimension( : , : , : ), intent(in)  h,
real, dimension(:), intent(out)  stock_values,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(tracer_flow_control_cs), pointer  CS,
character(len=*), dimension(:), intent(out), optional  stock_names,
character(len=*), dimension(:), intent(out), optional  stock_units,
integer, intent(out), optional  num_stocks,
integer, intent(in), optional  stock_index,
logical, dimension(:), intent(inout), optional  got_min_max,
real, dimension(:), intent(out), optional  global_min,
real, dimension(:), intent(out), optional  global_max,
real, dimension(:), intent(out), optional  xgmin,
real, dimension(:), intent(out), optional  ygmin,
real, dimension(:), intent(out), optional  zgmin,
real, dimension(:), intent(out), optional  xgmax,
real, dimension(:), intent(out), optional  ygmax,
real, dimension(:), intent(out), optional  zgmax 
)

This subroutine calls all registered tracer packages to enable them to add to the surface state returned to the coupler. These routines are optional.

Parameters
[in]hLayer thicknesses [H ~> m or kg m-2]
[out]stock_valuesThe integrated amounts of a tracer on the current PE, usually in kg x concentration [kg conc].
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
csThe control structure returned by a previous call to call_tracer_register.
[out]stock_namesDiagnostic names to use for each stock.
[out]stock_unitsUnits to use in the metadata for each stock.
[out]num_stocksThe number of tracer stocks being returned.
[in]stock_indexThe integer stock index from stocks_constants_mod of the stock to be returned. If this is present and greater than 0, only a single stock can be returned.
[in,out]got_min_maxIndicates whether the global min and
[out]global_minThe global minimum of each tracer
[out]global_maxThe global maximum of each tracer
[out]xgminThe x-position of the global minimum
[out]ygminThe y-position of the global minimum
[out]zgminThe z-position of the global minimum
[out]xgmaxThe x-position of the global maximum
[out]ygmaxThe y-position of the global maximum
[out]zgmaxThe z-position of the global maximum

Definition at line 574 of file MOM_tracer_flow_control.F90.

574  real, dimension(NIMEM_,NJMEM_,NKMEM_), &
575  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
576  real, dimension(:), intent(out) :: stock_values !< The integrated amounts of a tracer
577  !! on the current PE, usually in kg x concentration [kg conc].
578  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
579  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
580  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned by a
581  !! previous call to
582  !! call_tracer_register.
583  character(len=*), dimension(:), &
584  optional, intent(out) :: stock_names !< Diagnostic names to use for each stock.
585  character(len=*), dimension(:), &
586  optional, intent(out) :: stock_units !< Units to use in the metadata for each stock.
587  integer, optional, intent(out) :: num_stocks !< The number of tracer stocks being returned.
588  integer, optional, intent(in) :: stock_index !< The integer stock index from
589  !! stocks_constants_mod of the stock to be returned. If this is
590  !! present and greater than 0, only a single stock can be returned.
591  logical, dimension(:), &
592  optional, intent(inout) :: got_min_max !< Indicates whether the global min and
593  !! max are found for each tracer
594  real, dimension(:), optional, intent(out) :: global_min !< The global minimum of each tracer
595  real, dimension(:), optional, intent(out) :: global_max !< The global maximum of each tracer
596  real, dimension(:), optional, intent(out) :: xgmin !< The x-position of the global minimum
597  real, dimension(:), optional, intent(out) :: ygmin !< The y-position of the global minimum
598  real, dimension(:), optional, intent(out) :: zgmin !< The z-position of the global minimum
599  real, dimension(:), optional, intent(out) :: xgmax !< The x-position of the global maximum
600  real, dimension(:), optional, intent(out) :: ygmax !< The y-position of the global maximum
601  real, dimension(:), optional, intent(out) :: zgmax !< The z-position of the global maximum
602 
603  ! Local variables
604  character(len=200), dimension(MAX_FIELDS_) :: names, units
605  character(len=200) :: set_pkg_name
606  real, dimension(MAX_FIELDS_) :: values
607  integer :: max_ns, ns_tot, ns, index, pkg, max_pkgs, nn
608 
609  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_stocks: "// &
610  "Module must be initialized via call_tracer_register before it is used.")
611 
612  index = -1 ; if (present(stock_index)) index = stock_index
613  ns_tot = 0
614  max_ns = size(stock_values)
615  if (present(stock_names)) max_ns = min(max_ns,size(stock_names))
616  if (present(stock_units)) max_ns = min(max_ns,size(stock_units))
617 
618 ! Add other user-provided calls here.
619  if (cs%use_USER_tracer_example) then
620  ns = user_tracer_stock(h, values, g, gv, cs%USER_tracer_example_CSp, &
621  names, units, stock_index)
622  call store_stocks("tracer_example", ns, names, units, values, index, stock_values, &
623  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
624  endif
625 ! if (CS%use_DOME_tracer) then
626 ! ns = DOME_tracer_stock(h, values, G, GV, CS%DOME_tracer_CSp, &
627 ! names, units, stock_index)
628 ! call store_stocks("DOME_tracer", ns, names, units, values, index, stock_values, &
629 ! set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
630 ! endif
631  if (cs%use_ideal_age) then
632  ns = ideal_age_stock(h, values, g, gv, cs%ideal_age_tracer_CSp, &
633  names, units, stock_index)
634  call store_stocks("ideal_age_example", ns, names, units, values, index, &
635  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
636  endif
637  if (cs%use_regional_dyes) then
638  ns = dye_stock(h, values, g, gv, cs%dye_tracer_CSp, &
639  names, units, stock_index)
640  call store_stocks("regional_dyes", ns, names, units, values, index, &
641  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
642  endif
643  if (cs%use_oil) then
644  ns = oil_stock(h, values, g, gv, cs%oil_tracer_CSp, &
645  names, units, stock_index)
646  call store_stocks("oil_tracer", ns, names, units, values, index, &
647  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
648  endif
649  if (cs%use_OCMIP2_CFC) then
650  ns = ocmip2_cfc_stock(h, values, g, gv, cs%OCMIP2_CFC_CSp, names, units, stock_index)
651  call store_stocks("MOM_OCMIP2_CFC", ns, names, units, values, index, stock_values, &
652  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
653  endif
654 
655  if (cs%use_advection_test_tracer) then
656  ns = advection_test_stock( h, values, g, gv, cs%advection_test_tracer_CSp, &
657  names, units, stock_index )
658  call store_stocks("advection_test_tracer", ns, names, units, values, index, &
659  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
660  endif
661 
662 #ifdef _USE_GENERIC_TRACER
663  if (cs%use_MOM_generic_tracer) then
664  ns = mom_generic_tracer_stock(h, values, g, gv, cs%MOM_generic_tracer_CSp, &
665  names, units, stock_index)
666  call store_stocks("MOM_generic_tracer", ns, names, units, values, index, stock_values, &
667  set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
668  nn=ns_tot-ns+1
669  nn=mom_generic_tracer_min_max(nn, got_min_max, global_min, global_max, &
670  xgmin, ygmin, zgmin, xgmax, ygmax, zgmax ,&
671  g, cs%MOM_generic_tracer_CSp,names, units)
672 
673  endif
674 #endif
675  if (cs%use_pseudo_salt_tracer) then
676  ns = pseudo_salt_stock(h, values, g, gv, cs%pseudo_salt_tracer_CSp, &
677  names, units, stock_index)
678  call store_stocks("pseudo_salt_tracer", ns, names, units, values, index, &
679  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
680  endif
681 
682  if (cs%use_boundary_impulse_tracer) then
683  ns = boundary_impulse_stock(h, values, g, gv, cs%boundary_impulse_tracer_CSp, &
684  names, units, stock_index)
685  call store_stocks("boundary_impulse_tracer", ns, names, units, values, index, &
686  stock_values, set_pkg_name, max_ns, ns_tot, stock_names, stock_units)
687  endif
688 
689  if (ns_tot == 0) stock_values(1) = 0.0
690 
691  if (present(num_stocks)) num_stocks = ns_tot
692 

◆ call_tracer_surface_state()

subroutine, public mom_tracer_flow_control::call_tracer_surface_state ( type(surface), intent(inout)  state,
real, dimension( : , : , : ), intent(in)  h,
type(ocean_grid_type), intent(in)  G,
type(tracer_flow_control_cs), pointer  CS 
)

This subroutine calls all registered tracer packages to enable them to add to the surface state returned to the coupler. These routines are optional.

Parameters
[in,out]stateA structure containing fields that describe the surface state of the ocean.
[in]hLayer thicknesses [H ~> m or kg m-2]
[in]gThe ocean's grid structure.
csThe control structure returned by a previous call to call_tracer_register.

Definition at line 757 of file MOM_tracer_flow_control.F90.

757  type(surface), intent(inout) :: state !< A structure containing fields that
758  !! describe the surface state of the ocean.
759  real, dimension(NIMEM_,NJMEM_,NKMEM_), &
760  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
761  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
762  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned by a
763  !! previous call to call_tracer_register.
764 
765  if (.not. associated(cs)) call mom_error(fatal, "call_tracer_surface_state: "// &
766  "Module must be initialized via call_tracer_register before it is used.")
767 
768 ! Add other user-provided calls here.
769  if (cs%use_USER_tracer_example) &
770  call user_tracer_surface_state(state, h, g, cs%USER_tracer_example_CSp)
771  if (cs%use_DOME_tracer) &
772  call dome_tracer_surface_state(state, h, g, cs%DOME_tracer_CSp)
773  if (cs%use_ISOMIP_tracer) &
774  call isomip_tracer_surface_state(state, h, g, cs%ISOMIP_tracer_CSp)
775  if (cs%use_ideal_age) &
776  call ideal_age_tracer_surface_state(state, h, g, cs%ideal_age_tracer_CSp)
777  if (cs%use_regional_dyes) &
778  call dye_tracer_surface_state(state, h, g, cs%dye_tracer_CSp)
779  if (cs%use_oil) &
780  call oil_tracer_surface_state(state, h, g, cs%oil_tracer_CSp)
781  if (cs%use_advection_test_tracer) &
782  call advection_test_tracer_surface_state(state, h, g, cs%advection_test_tracer_CSp)
783  if (cs%use_OCMIP2_CFC) &
784  call ocmip2_cfc_surface_state(state, h, g, cs%OCMIP2_CFC_CSp)
785 #ifdef _USE_GENERIC_TRACER
786  if (cs%use_MOM_generic_tracer) &
787  call mom_generic_tracer_surface_state(state, h, g, cs%MOM_generic_tracer_CSp)
788 #endif
789 

◆ get_chl_from_model()

subroutine, public mom_tracer_flow_control::get_chl_from_model ( real, dimension( : , : , : ), intent(out)  Chl_array,
type(ocean_grid_type), intent(in)  G,
type(tracer_flow_control_cs), pointer  CS 
)

This subroutine extracts the chlorophyll concentrations from the model state, if possible.

Parameters
[out]chl_arrayThe array in which to store the model's
[in]gThe ocean's grid structure.
csThe control structure returned by a previous call to call_tracer_register.

Definition at line 361 of file MOM_tracer_flow_control.F90.

361  real, dimension(NIMEM_,NJMEM_,NKMEM_), &
362  intent(out) :: Chl_array !< The array in which to store the model's
363  !! Chlorophyll-A concentrations in mg m-3.
364  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
365  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned by a
366  !! previous call to call_tracer_register.
367 
368 #ifdef _USE_GENERIC_TRACER
369  if (cs%use_MOM_generic_tracer) then
370  call mom_generic_tracer_get('chl','field',chl_array, cs%MOM_generic_tracer_CSp)
371  else
372  call mom_error(fatal, "get_chl_from_model was called in a configuration "// &
373  "that is unable to provide a sensible model-based value.\n"// &
374  "CS%use_MOM_generic_tracer is false and no other viable options are on.")
375  endif
376 #else
377  call mom_error(fatal, "get_chl_from_model was called in a configuration "// &
378  "that is unable to provide a sensible model-based value.\n"// &
379  "_USE_GENERIC_TRACER is undefined and no other options "//&
380  "are currently viable.")
381 #endif
382 

◆ store_stocks()

subroutine mom_tracer_flow_control::store_stocks ( character(len=*), intent(in)  pkg_name,
integer, intent(in)  ns,
character(len=*), dimension(:), intent(in)  names,
character(len=*), dimension(:), intent(in)  units,
real, dimension(:), intent(in)  values,
integer, intent(in)  index,
real, dimension(:), intent(inout)  stock_values,
character(len=*), intent(inout)  set_pkg_name,
integer, intent(in)  max_ns,
integer, intent(inout)  ns_tot,
character(len=*), dimension(:), intent(inout), optional  stock_names,
character(len=*), dimension(:), intent(inout), optional  stock_units 
)
private

This routine stores the stocks and does error handling for call_tracer_stocks.

Parameters
[in]pkg_nameThe tracer package name
[in]nsThe number of stocks associated with this tracer package
[in]namesDiagnostic names to use for each stock.
[in]unitsUnits to use in the metadata for each stock.
[in]valuesThe values of the tracer stocks
[in]indexThe integer stock index from stocks_constants_mod of the stock to be returned. If this is present and greater than 0, only a single stock can be returned.
[in,out]stock_valuesThe master list of stock values
[in,out]set_pkg_nameThe name of the last tracer package whose stocks were stored for a specific index. This is used to trigger an error if there are redundant stocks.
[in]max_nsThe maximum size of the master stock list
[in,out]ns_totThe total number of stocks in the master list
[in,out]stock_namesDiagnostic names to use for each stock in the master list
[in,out]stock_unitsUnits to use in the metadata for each stock in the master list

Definition at line 698 of file MOM_tracer_flow_control.F90.

698  character(len=*), intent(in) :: pkg_name !< The tracer package name
699  integer, intent(in) :: ns !< The number of stocks associated with this tracer package
700  character(len=*), dimension(:), &
701  intent(in) :: names !< Diagnostic names to use for each stock.
702  character(len=*), dimension(:), &
703  intent(in) :: units !< Units to use in the metadata for each stock.
704  real, dimension(:), intent(in) :: values !< The values of the tracer stocks
705  integer, intent(in) :: index !< The integer stock index from
706  !! stocks_constants_mod of the stock to be returned. If this is
707  !! present and greater than 0, only a single stock can be returned.
708  real, dimension(:), intent(inout) :: stock_values !< The master list of stock values
709  character(len=*), intent(inout) :: set_pkg_name !< The name of the last tracer package whose
710  !! stocks were stored for a specific index. This is
711  !! used to trigger an error if there are redundant stocks.
712  integer, intent(in) :: max_ns !< The maximum size of the master stock list
713  integer, intent(inout) :: ns_tot !< The total number of stocks in the master list
714  character(len=*), dimension(:), &
715  optional, intent(inout) :: stock_names !< Diagnostic names to use for each stock in the master list
716  character(len=*), dimension(:), &
717  optional, intent(inout) :: stock_units !< Units to use in the metadata for each stock in the master list
718 
719 ! This routine stores the stocks and does error handling for call_tracer_stocks.
720  character(len=16) :: ind_text, ns_text, max_text
721  integer :: n
722 
723  if ((index > 0) .and. (ns > 0)) then
724  write(ind_text,'(i8)') index
725  if (ns > 1) then
726  call mom_error(fatal,"Tracer package "//trim(pkg_name)//&
727  " is not permitted to return more than one value when queried"//&
728  " for specific stock index "//trim(adjustl(ind_text))//".")
729  elseif (ns+ns_tot > 1) then
730  call mom_error(fatal,"Tracer packages "//trim(pkg_name)//" and "//&
731  trim(set_pkg_name)//" both attempted to set values for"//&
732  " specific stock index "//trim(adjustl(ind_text))//".")
733  else
734  set_pkg_name = pkg_name
735  endif
736  endif
737 
738  if (ns_tot+ns > max_ns) then
739  write(ns_text,'(i8)') ns_tot+ns ; write(max_text,'(i8)') max_ns
740  call mom_error(fatal,"Attempted to return more tracer stock values (at least "//&
741  trim(adjustl(ns_text))//") than the size "//trim(adjustl(max_text))//&
742  "of the smallest value, name, or units array.")
743  endif
744 
745  do n=1,ns
746  stock_values(ns_tot+n) = values(n)
747  if (present(stock_names)) stock_names(ns_tot+n) = names(n)
748  if (present(stock_units)) stock_units(ns_tot+n) = units(n)
749  enddo
750  ns_tot = ns_tot + ns
751 

◆ tracer_flow_control_end()

subroutine, public mom_tracer_flow_control::tracer_flow_control_end ( type(tracer_flow_control_cs), pointer  CS)
Parameters
csThe control structure returned by a previous call to call_tracer_register.

Definition at line 793 of file MOM_tracer_flow_control.F90.

793  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned by a
794  !! previous call to call_tracer_register.
795 
796  if (cs%use_USER_tracer_example) &
797  call user_tracer_example_end(cs%USER_tracer_example_CSp)
798  if (cs%use_DOME_tracer) call dome_tracer_end(cs%DOME_tracer_CSp)
799  if (cs%use_ISOMIP_tracer) call isomip_tracer_end(cs%ISOMIP_tracer_CSp)
800  if (cs%use_RGC_tracer) call rgc_tracer_end(cs%RGC_tracer_CSp)
801  if (cs%use_ideal_age) call ideal_age_example_end(cs%ideal_age_tracer_CSp)
802  if (cs%use_regional_dyes) call regional_dyes_end(cs%dye_tracer_CSp)
803  if (cs%use_oil) call oil_tracer_end(cs%oil_tracer_CSp)
804  if (cs%use_advection_test_tracer) call advection_test_tracer_end(cs%advection_test_tracer_CSp)
805  if (cs%use_OCMIP2_CFC) call ocmip2_cfc_end(cs%OCMIP2_CFC_CSp)
806 #ifdef _USE_GENERIC_TRACER
807  if (cs%use_MOM_generic_tracer) call end_mom_generic_tracer(cs%MOM_generic_tracer_CSp)
808 #endif
809  if (cs%use_pseudo_salt_tracer) call pseudo_salt_tracer_end(cs%pseudo_salt_tracer_CSp)
810  if (cs%use_boundary_impulse_tracer) call boundary_impulse_tracer_end(cs%boundary_impulse_tracer_CSp)
811  if (cs%use_dyed_obc_tracer) call dyed_obc_tracer_end(cs%dyed_obc_tracer_CSp)
812 
813  if (associated(cs)) deallocate(cs)

◆ tracer_flow_control_init()

subroutine, public mom_tracer_flow_control::tracer_flow_control_init ( logical, intent(in)  restart,
type(time_type), intent(in), target  day,
type(ocean_grid_type), intent(inout)  G,
type(verticalgrid_type), intent(in)  GV,
type(unit_scale_type), intent(in)  US,
real, dimension( : , : , : ), intent(in)  h,
type(param_file_type), intent(in)  param_file,
type(diag_ctrl), intent(in), target  diag,
type(ocean_obc_type), pointer  OBC,
type(tracer_flow_control_cs), pointer  CS,
type(sponge_cs), pointer  sponge_CSp,
type(ale_sponge_cs), pointer  ALE_sponge_CSp,
type(thermo_var_ptrs), intent(in)  tv 
)

This subroutine calls all registered tracer initialization subroutines.

Parameters
[in]restart1 if the fields have already been read from a restart file.
[in]dayTime of the start of the run.
[in,out]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
[in]usA dimensional unit scaling type
[in]hLayer thicknesses [H ~> m or kg m-2]
[in]param_fileA structure to parse for run-time parameters
[in]diagA structure that is used to regulate diagnostic output.
obcThis open boundary condition type specifies whether, where, and what open boundary conditions are used.
csThe control structure returned by a previous call to call_tracer_register.
sponge_cspA pointer to the control structure for the sponges, if they are in use. Otherwise this may be unassociated.
ale_sponge_cspA pointer to the control structure for the ALE sponges, if they are in use. Otherwise this may be unassociated.
[in]tvA structure pointing to various thermodynamic variables

Definition at line 284 of file MOM_tracer_flow_control.F90.

284  logical, intent(in) :: restart !< 1 if the fields have already
285  !! been read from a restart file.
286  type(time_type), target, intent(in) :: day !< Time of the start of the run.
287  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
288  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid
289  !! structure.
290  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
291  real, dimension(NIMEM_,NJMEM_,NKMEM_), intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
292  type(param_file_type), intent(in) :: param_file !< A structure to parse for
293  !! run-time parameters
294  type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to
295  !! regulate diagnostic output.
296  type(ocean_OBC_type), pointer :: OBC !< This open boundary condition
297  !! type specifies whether, where,
298  !! and what open boundary
299  !! conditions are used.
300  type(tracer_flow_control_CS), pointer :: CS !< The control structure returned
301  !! by a previous call to
302  !! call_tracer_register.
303  type(sponge_CS), pointer :: sponge_CSp !< A pointer to the control
304  !! structure for the sponges, if they are in use.
305  !! Otherwise this may be unassociated.
306  type(ALE_sponge_CS), pointer :: ALE_sponge_CSp !< A pointer to the control
307  !! structure for the ALE sponges, if they are in use.
308  !! Otherwise this may be unassociated.
309  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
310  !! thermodynamic variables
311 
312  if (.not. associated(cs)) call mom_error(fatal, "tracer_flow_control_init: "// &
313  "Module must be initialized via call_tracer_register before it is used.")
314 
315 ! Add other user-provided calls here.
316  if (cs%use_USER_tracer_example) &
317  call user_initialize_tracer(restart, day, g, gv, h, diag, obc, cs%USER_tracer_example_CSp, &
318  sponge_csp)
319  if (cs%use_DOME_tracer) &
320  call initialize_dome_tracer(restart, day, g, gv, us, h, diag, obc, cs%DOME_tracer_CSp, &
321  sponge_csp, param_file)
322  if (cs%use_ISOMIP_tracer) &
323  call initialize_isomip_tracer(restart, day, g, gv, h, diag, obc, cs%ISOMIP_tracer_CSp, &
324  ale_sponge_csp)
325  if (cs%use_RGC_tracer) &
326  call initialize_rgc_tracer(restart, day, g, gv, h, diag, obc, &
327  cs%RGC_tracer_CSp, sponge_csp, ale_sponge_csp)
328  if (cs%use_ideal_age) &
329  call initialize_ideal_age_tracer(restart, day, g, gv, us, h, diag, obc, cs%ideal_age_tracer_CSp, &
330  sponge_csp)
331  if (cs%use_regional_dyes) &
332  call initialize_dye_tracer(restart, day, g, gv, h, diag, obc, cs%dye_tracer_CSp, &
333  sponge_csp)
334  if (cs%use_oil) &
335  call initialize_oil_tracer(restart, day, g, gv, us, h, diag, obc, cs%oil_tracer_CSp, &
336  sponge_csp)
337  if (cs%use_advection_test_tracer) &
338  call initialize_advection_test_tracer(restart, day, g, gv, h, diag, obc, cs%advection_test_tracer_CSp, &
339  sponge_csp)
340  if (cs%use_OCMIP2_CFC) &
341  call initialize_ocmip2_cfc(restart, day, g, gv, us, h, diag, obc, cs%OCMIP2_CFC_CSp, &
342  sponge_csp)
343 #ifdef _USE_GENERIC_TRACER
344  if (cs%use_MOM_generic_tracer) &
345  call initialize_mom_generic_tracer(restart, day, g, gv, us, h, param_file, diag, obc, &
346  cs%MOM_generic_tracer_CSp, sponge_csp, ale_sponge_csp)
347 #endif
348  if (cs%use_pseudo_salt_tracer) &
349  call initialize_pseudo_salt_tracer(restart, day, g, gv, h, diag, obc, cs%pseudo_salt_tracer_CSp, &
350  sponge_csp, tv)
351  if (cs%use_boundary_impulse_tracer) &
352  call initialize_boundary_impulse_tracer(restart, day, g, gv, h, diag, obc, cs%boundary_impulse_tracer_CSp, &
353  sponge_csp, tv)
354  if (cs%use_dyed_obc_tracer) &
355  call initialize_dyed_obc_tracer(restart, day, g, gv, h, diag, obc, cs%dyed_obc_tracer_CSp)
356