MOM6
MOM_generic_tracer.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU General Public License *
3 !* This file is a part of MOM. *
4 !* *
5 !* MOM is free software; you can redistribute it and/or modify it and *
6 !* are expected to follow the terms of the GNU General Public License *
7 !* as published by the Free Software Foundation; either version 2 of *
8 !* the License, or (at your option) any later version. *
9 !* *
10 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
11 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
12 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
13 !* License for more details. *
14 !* *
15 !* For the full text of the GNU General Public License, *
16 !* write to: Free Software Foundation, Inc., *
17 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
18 !* or see: http://www.gnu.org/licenses/gpl.html *
19 !***********************************************************************
20 !----------------------------------------------------------------
21 ! <CONTACT EMAIL="Niki.Zadeh@noaa.gov"> Niki Zadeh
22 ! </CONTACT>
23 !
24 ! <REVIEWER EMAIL="William.Cooke@noaa.gov"> William Cooke
25 ! </REVIEWER>
26 !
27 ! <OVERVIEW>
28 ! This module drives the generic version of tracers TOPAZ and CFC
29 ! </OVERVIEW>
30 !----------------------------------------------------------------
31 
32 #include <MOM_memory.h>
33 
35 
36 #ifdef _USE_GENERIC_TRACER
37 #include <fms_platform.h>
38 
39  use mpp_mod, only: stdout, mpp_error, fatal,warning,note
40  use field_manager_mod, only: fm_get_index,fm_string_len
41 
42  use generic_tracer, only: generic_tracer_register, generic_tracer_get_diag_list
43  use generic_tracer, only: generic_tracer_init, generic_tracer_source, generic_tracer_register_diag
44  use generic_tracer, only: generic_tracer_coupler_get, generic_tracer_coupler_set
45  use generic_tracer, only: generic_tracer_end, generic_tracer_get_list, do_generic_tracer
46  use generic_tracer, only: generic_tracer_update_from_bottom,generic_tracer_vertdiff_g
47  use generic_tracer, only: generic_tracer_coupler_accumulate
48 
49  use g_tracer_utils, only: g_tracer_get_name,g_tracer_set_values,g_tracer_set_common,g_tracer_get_common
50  use g_tracer_utils, only: g_tracer_get_next,g_tracer_type,g_tracer_is_prog,g_tracer_flux_init
51  use g_tracer_utils, only: g_tracer_send_diag,g_tracer_get_values
52  use g_tracer_utils, only: g_tracer_get_pointer,g_tracer_get_alias,g_diag_type,g_tracer_set_csdiag
53 
54  use mom_diag_mediator, only : post_data, register_diag_field, safe_alloc_ptr
57  use mom_error_handler, only : mom_error, fatal, warning, note, is_root_pe
59  use mom_forcing_type, only : forcing, optics_type
60  use mom_grid, only : ocean_grid_type
61  use mom_hor_index, only : hor_index_type
62  use mom_io, only : file_exists, read_data, slasher, vardesc, var_desc
67  use mom_time_manager, only : time_type, get_time, set_time
72  use mom_tracer_initialization_from_z, only : mom_initialize_tracer_from_z
76 
77 
78  implicit none ; private
79  logical :: g_registered = .false.
80 
81  public register_mom_generic_tracer, initialize_mom_generic_tracer
82  public mom_generic_tracer_column_physics, mom_generic_tracer_surface_state
83  public end_mom_generic_tracer, mom_generic_tracer_get
84  public mom_generic_tracer_stock
85  public mom_generic_flux_init
86  public mom_generic_tracer_min_max
87  public mom_generic_tracer_fluxes_accumulate
88 
89  type, public :: mom_generic_tracer_cs ; private
90  character(len = 200) :: ic_file ! The file in which the generic tracer initial values can
91  ! be found, or an empty string for internal initialization.
92  logical :: z_ic_file ! If true, the generic_tracer IC_file is in Z-space. The default is false.
93  real :: tracer_ic_val = 0.0 ! The initial value assigned to tracers.
94  real :: tracer_land_val = -1.0 ! The values of tracers used where land is masked out.
95  logical :: tracers_may_reinit ! If true, tracers may go through the
96  ! initialization code if they are not found in the
97  ! restart files.
98 
99  type(diag_ctrl), pointer :: diag ! A structure that is used to regulate the
100  ! timing of diagnostic output.
101  type(mom_restart_cs), pointer :: restart_csp => null()
102 
103  ! The following pointer will be directed to the first element of the
104  ! linked list of generic tracers.
105  type(g_tracer_type), pointer :: g_tracer_list => null()
106  ! The following pointer will be directed to the first element of the
107  ! linked list of generic diagnostics fields that must be Z registered by MOM.
108  type(g_diag_type), pointer :: g_diag_list => null()
109 
110  integer :: h_to_m !Auxiliary to access GV%H_to_m in routines that do not have access to GV
111 
112  end type mom_generic_tracer_cs
113 
114 ! This include declares and sets the variable "version".
115 #include "version_variable.h"
116 
117 contains
118 
119  ! <SUBROUTINE NAME="register_MOM_generic_tracer">
120  ! <OVERVIEW>
121  ! Initialize phase I: Add the generic tracers
122  ! </OVERVIEW>
123  ! <DESCRIPTION>
124  ! This subroutine:
125  ! Initializes the generic tracer packages and adds their tracers to the list
126  ! Adds the tracers in the list of generic tracers to the set of MOM tracers (i.e., MOM-register them)
127  ! Register these tracers for restart
128  ! </DESCRIPTION>
129  ! <TEMPLATE>
130  ! call register_MOM_generic_tracer(G, param_file, CS, diag, tr_Reg, restart_CS)
131  ! </TEMPLATE>
132  ! </SUBROUTINE>
133 
134  function register_mom_generic_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
135  type(hor_index_type), intent(in) :: hi
136  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
137  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
138  type(mom_generic_tracer_cs), pointer :: cs
139  type(tracer_registry_type), pointer :: tr_reg
140  type(mom_restart_cs), pointer :: restart_cs
141  ! This subroutine is used to register tracer fields and subroutines
142  ! to be used with MOM.
143  ! Arguments: G - The ocean's grid structure.
144  ! (in) param_file - A structure indicating the open file to parse for
145  ! model parameter values.
146  ! (in/out) CS - A pointer that is set to point to the control structure
147  ! for this module
148  ! (in) diag - A structure that is used to regulate diagnostic output.
149  ! (in/out) tr_Reg - A pointer that is set to point to the control structure
150  ! for the tracer advection and diffusion module.
151  ! (in) restart_CS - A pointer to the restart control structure.
152  logical :: register_mom_generic_tracer
153 
154 
155  character(len=fm_string_len), parameter :: sub_name = 'register_MOM_generic_tracer'
156  character(len=200) :: inputdir ! The directory where NetCDF input files are.
157  ! These can be overridden later in via the field manager?
158 
159  integer :: ntau, k,i,j,axes(3)
160  type(g_tracer_type), pointer :: g_tracer,g_tracer_next
161  character(len=fm_string_len) :: g_tracer_name,longname,units
162  real, dimension(:,:,:,:), pointer :: tr_field
163  real, dimension(:,:,:), pointer :: tr_ptr
164  real, dimension(HI%isd:HI%ied, HI%jsd:HI%jed,GV%ke) :: grid_tmask
165  integer, dimension(HI%isd:HI%ied, HI%jsd:HI%jed) :: grid_kmt
166  type(vardesc) :: vdesc
167 
168  register_mom_generic_tracer = .false.
169  if (associated(cs)) then
170  call mpp_error(warning, "register_MOM_generic_tracer called with an "// &
171  "associated control structure.")
172  return
173  endif
174  allocate(cs)
175 
176 
177  !Register all the generic tracers used and create the list of them.
178  !This can be called by ALL PE's. No array fields allocated.
179  if (.not. g_registered) then
180  call generic_tracer_register
181  g_registered = .true.
182  endif
183 
184 
185  ! Read all relevant parameters and write them to the model log.
186  call log_version(param_file, sub_name, version, "")
187  call get_param(param_file, sub_name, "GENERIC_TRACER_IC_FILE", cs%IC_file, &
188  "The file in which the generic trcer initial values can \n"//&
189  "be found, or an empty string for internal initialization.", &
190  default=" ")
191  if ((len_trim(cs%IC_file) > 0) .and. (scan(cs%IC_file,'/') == 0)) then
192  ! Add the directory if CS%IC_file is not already a complete path.
193  call get_param(param_file, sub_name, "INPUTDIR", inputdir, default=".")
194  cs%IC_file = trim(slasher(inputdir))//trim(cs%IC_file)
195  call log_param(param_file, sub_name, "INPUTDIR/GENERIC_TRACER_IC_FILE", cs%IC_file)
196  endif
197  call get_param(param_file, sub_name, "GENERIC_TRACER_IC_FILE_IS_Z", cs%Z_IC_file, &
198  "If true, GENERIC_TRACER_IC_FILE is in depth space, not \n"//&
199  "layer space.",default=.false.)
200  call get_param(param_file, sub_name, "TRACERS_MAY_REINIT", cs%tracers_may_reinit, &
201  "If true, tracers may go through the initialization code \n"//&
202  "if they are not found in the restart files. Otherwise \n"//&
203  "it is a fatal error if tracers are not found in the \n"//&
204  "restart files of a restarted run.", default=.false.)
205 
206  cs%restart_CSp => restart_cs
207 
208 
209  ntau=1 ! MOM needs the fields at only one time step
210 
211 
212  ! At this point G%mask2dT and CS%diag%axesTL are not allocated.
213  ! postpone diag_registeration to initialize_MOM_generic_tracer
214 
215  !Fields cannot be diag registered as they are allocated and have to registered later.
216  grid_tmask(:,:,:) = 0.0
217  grid_kmt(:,:) = 0.0
218  axes(:) = -1
219 
220  !
221  ! Initialize all generic tracers
222  !
223  call generic_tracer_init(hi%isc,hi%iec,hi%jsc,hi%jec,hi%isd,hi%ied,hi%jsd,hi%jed,&
224  gv%ke,ntau,axes,grid_tmask,grid_kmt,set_time(0,0))
225 
226 
227  !
228  ! MOM-register the generic tracers
229  !
230 
231  !Get the tracer list
232  call generic_tracer_get_list(cs%g_tracer_list)
233  if(.NOT. associated(cs%g_tracer_list)) call mpp_error(fatal, trim(sub_name)//&
234  ": No tracer in the list.")
235  ! For each tracer name get its T_prog index and get its fields
236 
237  g_tracer=>cs%g_tracer_list
238  do
239  call g_tracer_get_alias(g_tracer,g_tracer_name)
240 
241  call g_tracer_get_pointer(g_tracer,g_tracer_name,'field',tr_field)
242  call g_tracer_get_values(g_tracer,g_tracer_name,'longname', longname)
243  call g_tracer_get_values(g_tracer,g_tracer_name,'units',units )
244 
245  !nnz: Hard coded stuff. Need get/set routines
246  vdesc = var_desc(g_tracer_name, units, longname, &
247  caller="MOM_generic_tracer")
248  !!nnz: MOM field is 3D. Does this affect performance? Need it be override field?
249  tr_ptr => tr_field(:,:,:,1)
250  ! Register tracer for restart file.
251  ! mandatory field in restart file is set to .false.
252  ! 2008/12/08 jgj: change default to true, so all fields must be present in restart.
253  ! 2010/02/04 jgj: if tracers_may_reinit is true, tracers may go through
254  ! initialization code if not found in restart
255  call register_restart_field(tr_ptr, vdesc, .not.cs%tracers_may_reinit, restart_cs)
256 
257  ! Register prognastic tracer for horizontal advection & diffusion. Note
258  ! that because the generic tracer code uses only a temporary copy of
259  ! the vardesc type, a pointer to this type can not be set as a target
260  ! for register_tracer to use.
261  if (g_tracer_is_prog(g_tracer)) &
262  call register_tracer(tr_ptr, vdesc, param_file, hi, gv, tr_reg)
263 
264  !traverse the linked list till hit NULL
265  call g_tracer_get_next(g_tracer, g_tracer_next)
266  if(.NOT. associated(g_tracer_next)) exit
267  g_tracer=>g_tracer_next
268 
269  enddo
270 
271  register_mom_generic_tracer = .true.
272  end function register_mom_generic_tracer
273 
274  ! <SUBROUTINE NAME="initialize_MOM_generic_tracer">
275  ! <OVERVIEW>
276  ! Initialize phase II: Initialize required variables for generic tracers
277  ! </OVERVIEW>
278  ! <DESCRIPTION>
279  ! There are some steps of initialization that cannot be done in register_MOM_generic_tracer
280  ! This is the place and time to do them:
281  ! Set the grid mask and initial time for all generic tracers.
282  ! Diag_register them.
283  ! Z_diag_register them.
284  ! </DESCRIPTION>
285  ! <TEMPLATE>
286  ! call initialize_MOM_generic_tracer(restart, day, G, h, OBC, CS, sponge_CSp,ALE_sponge_CSp, diag_to_Z_CSp)
287  ! </SUBROUTINE>
288  subroutine initialize_mom_generic_tracer(restart, day, G, GV, h, param_file, diag, OBC, CS, &
289  sponge_CSp, ALE_sponge_CSp,diag_to_Z_CSp)
290  logical, intent(in) :: restart
291  type(time_type), target, intent(in) :: day
292  type(ocean_grid_type), intent(inout) :: g !< The ocean's grid structure
293  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
294  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
295  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
296  type(diag_ctrl), target, intent(in) :: diag
297  type(ocean_obc_type), pointer :: obc
298  type(mom_generic_tracer_cs), pointer :: cs
299  type(sponge_cs), pointer :: sponge_csp
300  type(ale_sponge_cs), pointer :: ale_sponge_csp
301  type(diag_to_z_cs), pointer :: diag_to_z_csp
302  ! This subroutine initializes the NTR tracer fields in tr(:,:,:,:)
303  ! and it sets up the tracer output.
304 
305  ! Arguments: restart - .true. if the fields have already been read from
306  ! a restart file.
307  ! (in) day - Time of the start of the run.
308  ! (in) G - The ocean's grid structure.
309  ! (in) GV - The ocean's vertical grid structure.
310  ! (in) h - Layer thickness, in m or kg m-2.
311  ! (in) OBC - This open boundary condition type specifies whether, where,
312  ! and what open boundary conditions are used.
313  ! (in/out) CS - The control structure returned by a previous call to
314  ! register_MOM_generic_tracer.
315  ! (in/out) sponge_CSp - A pointer to the control structure for the sponges, if
316  ! they are in use. Otherwise this may be unassociated.
317  ! (in/out) ALE_sponge_CSp - A pointer to the control structure for the ALE
318  ! sponges, if they are in use. Otherwise this may be unassociated
319  ! (in/out) diag_to_Z_Csp - A pointer to the control structure for diagnostics
320  ! in depth space.
321 
322  character(len=fm_string_len), parameter :: sub_name = 'initialize_MOM_generic_tracer'
323  logical :: ok
324  integer :: i, j, k, isc, iec, jsc, jec, nk
325  type(g_tracer_type), pointer :: g_tracer,g_tracer_next
326  type(g_diag_type) , pointer :: g_diag,g_diag_next
327  character(len=fm_string_len) :: g_tracer_name, longname, units
328  real, dimension(:,:,:,:), pointer :: tr_field
329  real, dimension(:,:,:), pointer :: tr_ptr
330  real, dimension(G%isd:G%ied, G%jsd:G%jed,1:G%ke) :: grid_tmask
331  integer, dimension(G%isd:G%ied, G%jsd:G%jed) :: grid_kmt
332 
333  !! 2010/02/04 Add code to re-initialize Generic Tracers if needed during a model simulation
334  !! By default, restart cpio should not contain a Generic Tracer IC file and step below will be skipped.
335  !! Ideally, the generic tracer IC file should have the tracers on Z levels.
336 
337  isc = g%isc ; iec = g%iec ; jsc = g%jsc ; jec = g%jec ; nk = g%ke
338 
339  cs%diag=>diag
340  !Get the tracer list
341  if(.NOT. associated(cs%g_tracer_list)) call mpp_error(fatal, trim(sub_name)//&
342  ": No tracer in the list.")
343  !For each tracer name get its fields
344  g_tracer=>cs%g_tracer_list
345 
346  do
347  if(index(cs%IC_file, '_NULL_') .ne. 0) then
348  call mom_error(warning,"The name of the IC_file "//trim(cs%IC_file)//&
349  " indicates no MOM initialization was asked for the generic tracers."//&
350  "Bypassing the MOM initialization of ALL generic tracers!")
351  exit
352  endif
353  call g_tracer_get_alias(g_tracer,g_tracer_name)
354  call g_tracer_get_pointer(g_tracer,g_tracer_name,'field',tr_field)
355  tr_ptr => tr_field(:,:,:,1)
356 
357  if (.not.restart .or. (cs%tracers_may_reinit .and. &
358  .not.query_initialized(tr_ptr, g_tracer_name, cs%restart_CSp))) then
359 
360  if(g_tracer%requires_src_info ) then
361  call mom_error(note,"initialize_MOM_generic_tracer: "//&
362  "initializing generic tracer "//trim(g_tracer_name)//&
363  " using MOM_initialize_tracer_from_Z ")
364 
365  call mom_initialize_tracer_from_z(h, tr_ptr, g, gv, param_file, &
366  src_file = g_tracer%src_file, &
367  src_var_nam = g_tracer%src_var_name, &
368  src_var_unit_conversion = g_tracer%src_var_unit_conversion,&
369  src_var_record = g_tracer%src_var_record, &
370  src_var_gridspec = g_tracer%src_var_gridspec )
371 
372  !Check/apply the bounds for each g_tracer
373  do k=1,nk ; do j=jsc,jec ; do i=isc,iec
374  if(tr_ptr(i,j,k) .ne. cs%tracer_land_val) then
375  if(tr_ptr(i,j,k) .lt. g_tracer%src_var_valid_min) tr_ptr(i,j,k) = g_tracer%src_var_valid_min
376  !Jasmin does not want to apply the maximum for now
377  !if(tr_ptr(i,j,k) .gt. g_tracer%src_var_valid_max) tr_ptr(i,j,k) = g_tracer%src_var_valid_max
378  endif
379  enddo; enddo ; enddo
380 
381  !jgj: Reset CASED to 0 below K=1
382  if(trim(g_tracer_name) .eq. 'cased') then
383  do k=2,nk ; do j=jsc,jec ; do i=isc,iec
384  if(tr_ptr(i,j,k) .ne. cs%tracer_land_val) then
385  tr_ptr(i,j,k) = 0.0
386  endif
387  enddo; enddo ; enddo
388  endif
389 
390  else !Do it old way if the tracer is not registered to start from a specific source file.
391  !This path should be deprecated if all generic tracers are required to start from specified sources.
392  if (len_trim(cs%IC_file) > 0) then
393  ! Read the tracer concentrations from a netcdf file.
394  if (.not.file_exists(cs%IC_file)) call mom_error(fatal, &
395  "initialize_MOM_Generic_tracer: Unable to open "//cs%IC_file)
396  if (cs%Z_IC_file) then
397  ok = tracer_z_init(tr_ptr, h, cs%IC_file, g_tracer_name, g)
398  if (.not.ok) then
399  ok = tracer_z_init(tr_ptr, h, cs%IC_file, trim(g_tracer_name), g)
400  if (.not.ok) call mom_error(fatal,"initialize_MOM_Generic_tracer: "//&
401  "Unable to read "//trim(g_tracer_name)//" from "//&
402  trim(cs%IC_file)//".")
403  endif
404  call mom_error(note,"initialize_MOM_generic_tracer: "//&
405  "initialized generic tracer "//trim(g_tracer_name)//&
406  " using Generic Tracer File on Z: "//cs%IC_file)
407  else
408  ! native grid
409  call mom_error(note,"initialize_MOM_generic_tracer: "//&
410  "Using Generic Tracer IC file on native grid "//trim(cs%IC_file)//&
411  " for tracer "//trim(g_tracer_name))
412  call read_data(cs%IC_file, trim(g_tracer_name), tr_ptr, domain=g%Domain%mpp_domain)
413  endif
414  else
415  call mom_error(fatal,"initialize_MOM_generic_tracer: "//&
416  "check Generic Tracer IC filename "//trim(cs%IC_file)//".")
417  endif
418 
419  endif
420  endif
421 
422  !traverse the linked list till hit NULL
423  call g_tracer_get_next(g_tracer, g_tracer_next)
424  if(.NOT. associated(g_tracer_next)) exit
425  g_tracer=>g_tracer_next
426  enddo
427  !! end section to re-initialize generic tracers
428 
429 
430  !Now we can reset the grid mask, axes and time to their true values
431  !Note that grid_tmask must be set correctly on the data domain boundary
432  !so that coast mask can be deduced from it.
433  grid_tmask(:,:,:) = 0.0
434  grid_kmt(:,:) = 0
435  do j = g%jsd, g%jed ; do i = g%isd, g%ied
436  if (g%mask2dT(i,j) .gt. 0) then
437  grid_tmask(i,j,:) = 1.0
438  grid_kmt(i,j) = g%ke ! Tell the code that a layer thicker than 1m is the bottom layer.
439  endif
440  enddo ; enddo
441  call g_tracer_set_common(g%isc,g%iec,g%jsc,g%jec,g%isd,g%ied,g%jsd,g%jed,&
442  gv%ke,1,cs%diag%axesTL%handles,grid_tmask,grid_kmt,day)
443 
444  ! Register generic tracer modules diagnostics
445 
446 #ifdef _USE_MOM6_DIAG
447  call g_tracer_set_csdiag(cs%diag)
448 #endif
449  call generic_tracer_register_diag()
450 #ifdef _USE_MOM6_DIAG
451  call g_tracer_set_csdiag(cs%diag)
452 #endif
453 
454 
455  ! Register Z diagnostic output.
456  !Get the tracer list
457  if(.NOT. associated(cs%g_tracer_list)) call mpp_error(fatal, trim(sub_name)//&
458  ": No tracer in the list.")
459  !For each tracer name get its fields
460  g_tracer=>cs%g_tracer_list
461  do
462  call g_tracer_get_alias(g_tracer,g_tracer_name)
463 
464  call g_tracer_get_pointer(g_tracer,g_tracer_name,'field',tr_field)
465  tr_ptr => tr_field(:,:,:,1)
466  call g_tracer_get_values(g_tracer,g_tracer_name,'longname', longname)
467  call g_tracer_get_values(g_tracer,g_tracer_name,'units',units )
468 
469  call register_z_tracer(tr_ptr, trim(g_tracer_name),longname , units, &
470  day, g, diag_to_z_csp)
471 
472  !traverse the linked list till hit NULL
473  call g_tracer_get_next(g_tracer, g_tracer_next)
474  if(.NOT. associated(g_tracer_next)) exit
475  g_tracer=>g_tracer_next
476 
477  enddo
478 
479  !For each special diagnostics name get its fields
480  !Get the diag list
481  call generic_tracer_get_diag_list(cs%g_diag_list)
482  if(associated(cs%g_diag_list)) then
483  g_diag=>cs%g_diag_list
484  do
485  if(g_diag%Z_diag .ne. 0) &
486  call register_z_tracer(g_diag%field_ptr, trim(g_diag%name),g_diag%longname , g_diag%units, &
487  day, g, diag_to_z_csp)
488 
489  !traverse the linked list till hit NULL
490  g_diag=>g_diag%next
491  if(.NOT. associated(g_diag)) exit
492 
493  enddo
494  endif
495 
496  cs%H_to_m = gv%H_to_m
497 
498  end subroutine initialize_mom_generic_tracer
499 
500  ! <SUBROUTINE NAME="MOM_generic_tracer_column_physics">
501  ! <OVERVIEW>
502  ! Column physics for generic tracers.
503  ! </OVERVIEW>
504  ! <DESCRIPTION>
505  ! This subroutine does:
506  ! Get the coupler values for generic tracers that exchange with atmosphere
507  ! Update generic tracer concentration fields from sources and sinks.
508  ! Vertically diffuse generic tracer concentration fields.
509  ! Update generic tracers from bottom and their bottom reservoir.
510  ! </DESCRIPTION>
511  ! <TEMPLATE>
512  ! call MOM_generic_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, CS, tv, optics)
513  ! </TEMPLATE>
514  ! </SUBROUTINE>
515 
516  subroutine mom_generic_tracer_column_physics(h_old, h_new, ea, eb, fluxes, Hml, dt, G, GV, CS, tv, optics, &
517  evap_CFL_limit, minimum_forcing_depth)
518  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
519  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
520  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h_old, h_new, ea, eb
521  type(forcing), intent(in) :: fluxes
522  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: hml !< Mixed layer depth
523  real, intent(in) :: dt !< The amount of time covered by this call, in s
524  type(mom_generic_tracer_cs), pointer :: cs
525  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic variables
526  type(optics_type), intent(in) :: optics
527  real, optional,intent(in) :: evap_cfl_limit
528  real, optional,intent(in) :: minimum_forcing_depth
529  ! This subroutine applies diapycnal diffusion and any other column
530  ! tracer physics or chemistry to the tracers from this file.
531  ! CFCs are relatively simple, as they are passive tracers. with only a surface
532  ! flux as a source.
533 
534  ! Arguments: h_old - Layer thickness before entrainment, in m or kg m-2.
535  ! (in) h_new - Layer thickness after entrainment, in m or kg m-2.
536  ! (in) ea - an array to which the amount of fluid entrained
537  ! from the layer above during this call will be
538  ! added, in m or kg m-2.
539  ! (in) eb - an array to which the amount of fluid entrained
540  ! from the layer below during this call will be
541  ! added, in m or kg m-2.
542  ! (in) fluxes - A structure containing pointers to any possible
543  ! forcing fields. Unused fields have NULL ptrs.
544  ! (in) dt - The amount of time covered by this call, in s.
545  ! (in) G - The ocean's grid structure.
546  ! (in) GV - The ocean's vertical grid structure.
547  ! (in) CS - The control structure returned by a previous call to
548  ! register_MOM_generic_tracer.
549  ! (in) evap_CFL_limit - Limits how much water can be fluxed out of the top layer
550  ! Stored previously in diabatic CS.
551  ! (in) minimum_forcing_depth - The smallest depth over which fluxes can be applied
552  ! Stored previously in diabatic CS.
553  !
554  ! The arguments to this subroutine are redundant in that
555  ! h_new[k] = h_old[k] + ea[k] - eb[k-1] + eb[k] - ea[k+1]
556  character(len=fm_string_len), parameter :: sub_name = 'MOM_generic_tracer_column_physics'
557 
558  type(g_tracer_type), pointer :: g_tracer, g_tracer_next
559  character(len=fm_string_len) :: g_tracer_name
560  real, dimension(:,:), pointer :: stf_array,trunoff_array,runoff_tracer_flux_array
561 
562  real :: surface_field(szi_(g),szj_(g))
563  real :: sosga
564 
565  real, dimension(G%isd:G%ied,G%jsd:G%jed,G%ke) :: rho_dzt, dzt
566  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_work
567  integer :: i, j, k, isc, iec, jsc, jec, nk
568 
569  isc = g%isc ; iec = g%iec ; jsc = g%jsc ; jec = g%jec ; nk = g%ke
570 
571  !Get the tracer list
572  if(.NOT. associated(cs%g_tracer_list)) call mpp_error(fatal,&
573  trim(sub_name)//": No tracer in the list.")
574 
575 #ifdef _USE_MOM6_DIAG
576  call g_tracer_set_csdiag(cs%diag)
577 #endif
578 
579  !
580  !Extract the tracer surface fields from coupler and update tracer fields from sources
581  !
582  !call generic_tracer_coupler_get(fluxes%tr_fluxes)
583  !Niki: This is moved out to ocean_model_MOM.F90 because if dt_therm>dt_cpld we need to average
584  ! the fluxes without coming into this subroutine.
585  ! MOM5 has to modified to conform.
586 
587  !
588  !Add contribution of river to surface flux
589  !
590  g_tracer=>cs%g_tracer_list
591  do
592  if(_allocated(g_tracer%trunoff)) then
593  call g_tracer_get_alias(g_tracer,g_tracer_name)
594  call g_tracer_get_pointer(g_tracer,g_tracer_name,'stf', stf_array)
595  call g_tracer_get_pointer(g_tracer,g_tracer_name,'trunoff',trunoff_array)
596  call g_tracer_get_pointer(g_tracer,g_tracer_name,'runoff_tracer_flux',runoff_tracer_flux_array)
597  !nnz: Why is fluxes%river = 0?
598  runoff_tracer_flux_array = trunoff_array * fluxes%lrunoff
599  stf_array = stf_array + runoff_tracer_flux_array
600  endif
601 
602  !traverse the linked list till hit NULL
603  call g_tracer_get_next(g_tracer, g_tracer_next)
604  if(.NOT. associated(g_tracer_next)) exit
605  g_tracer=>g_tracer_next
606 
607  enddo
608 
609  !
610  !Prepare input arrays for source update
611  !
612 
613  rho_dzt(:,:,:) = gv%H_to_kg_m2 * gv%Angstrom
614  do k = 1, nk ; do j = jsc, jec ; do i = isc, iec !{
615  rho_dzt(i,j,k) = gv%H_to_kg_m2 * h_old(i,j,k)
616  enddo; enddo ; enddo !}
617 
618  dzt(:,:,:) = 1.0
619  do k = 1, nk ; do j = jsc, jec ; do i = isc, iec !{
620  dzt(i,j,k) = gv%H_to_m * h_old(i,j,k)
621  enddo; enddo ; enddo !}
622 
623  do j=jsc,jec ; do i=isc,iec
624  surface_field(i,j) = tv%S(i,j,1)
625  enddo ; enddo
626  sosga = global_area_mean(surface_field, g)
627 
628  !
629  !Calculate tendencies (i.e., field changes at dt) from the sources / sinks
630  !
631 
632  call generic_tracer_source(tv%T,tv%S,rho_dzt,dzt,hml,g%isd,g%jsd,1,dt,&
633  g%areaT,get_diag_time_end(cs%diag),&
634  optics%nbands, optics%max_wavelength_band, optics%sw_pen_band, optics%opacity_band, sosga=sosga)
635 
636  ! This uses applyTracerBoundaryFluxesInOut to handle the change in tracer due to freshwater fluxes
637  ! usually in ALE mode
638  if (present(evap_cfl_limit) .and. present(minimum_forcing_depth)) then
639  g_tracer=>cs%g_tracer_list
640  do
641  if (g_tracer_is_prog(g_tracer)) then
642  do k=1,nk ;do j=jsc,jec ; do i=isc,iec
643  h_work(i,j,k) = h_old(i,j,k)
644  enddo ; enddo ; enddo;
645  call applytracerboundaryfluxesinout(g, gv, g_tracer%field(:,:,:,1), dt, fluxes, h_work, &
646  evap_cfl_limit, minimum_forcing_depth)
647  endif
648 
649  !traverse the linked list till hit NULL
650  call g_tracer_get_next(g_tracer, g_tracer_next)
651  if(.NOT. associated(g_tracer_next)) exit
652  g_tracer=>g_tracer_next
653  enddo
654  endif
655 
656  !
657  !Update Tr(n)%field from explicit vertical diffusion
658  !
659  ! Use a tridiagonal solver to determine the concentrations after the
660  ! surface source is applied and diapycnal advection and diffusion occurs.
661  if (present(evap_cfl_limit) .and. present(minimum_forcing_depth)) then
662  call generic_tracer_vertdiff_g(h_work, ea, eb, dt, gv%kg_m2_to_H, gv%m_to_H, 1) !Last arg is tau which is always 1 for MOM
663  else
664  call generic_tracer_vertdiff_g(h_old, ea, eb, dt, gv%kg_m2_to_H, gv%m_to_H, 1) !Last arg is tau which is always 1 for MOM
665  endif
666 
667  ! Update bottom fields after vertical processes
668 
669  call generic_tracer_update_from_bottom(dt, 1, get_diag_time_end(cs%diag)) !Second arg is tau which is always 1 for MOM
670 
671  !Output diagnostics via diag_manager for all generic tracers and their fluxes
672  call g_tracer_send_diag(cs%g_tracer_list, get_diag_time_end(cs%diag), tau=1)
673 #ifdef _USE_MOM6_DIAG
674  call g_tracer_set_csdiag(cs%diag)
675 #endif
676 
677 
678  end subroutine mom_generic_tracer_column_physics
679 
680  ! <SUBROUTINE NAME="MOM_generic_tracer_stock">
681  ! <OVERVIEW>
682  ! Calculate the mass-weighted integral of tracer concentrations.
683  ! </OVERVIEW>
684  ! <DESCRIPTION>
685  ! This subroutine calculates mass-weighted integral on the PE either
686  ! of all available tracer concentrations, or of a tracer that is
687  ! being requested specifically, returning the number of stocks it has
688  ! calculated.
689  ! </DESCRIPTION>
690  ! <TEMPLATE>
691  ! ns = MOM_generic_tracer_stock(h, stocks, G, CS, names, units, stock_index)
692  ! </TEMPLATE>
693  ! </SUBROUTINE>
694 
695  function mom_generic_tracer_stock(h, stocks, G, GV, CS, names, units, stock_index)
696  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
697  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
698  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
699  real, dimension(:), intent(out) :: stocks
700  type(mom_generic_tracer_cs), pointer :: cs
701  character(len=*), dimension(:), intent(out) :: names
702  character(len=*), dimension(:), intent(out) :: units
703  integer, optional, intent(in) :: stock_index
704  integer :: mom_generic_tracer_stock
705  ! This function calculates the mass-weighted integral of all tracer stocks,
706  ! returning the number of stocks it has calculated. If the stock_index
707  ! is present, only the stock corresponding to that coded index is returned.
708 
709  ! Arguments: h - Layer thickness, in m or kg m-2.
710  ! (out) stocks - the mass-weighted integrated amount of each tracer,
711  ! in kg times concentration units.
712  ! (in) G - The ocean's grid structure.
713  ! (in) GV - The ocean's vertical grid structure.
714  ! (in) CS - The control structure returned by a previous call to
715  ! register_MOM_generic_tracer.
716  ! (out) names - the names of the stocks calculated.
717  ! (out) units - the units of the stocks calculated.
718  ! (in,opt) stock_index - the coded index of a specific stock being sought.
719  ! Return value: the number of stocks calculated here.
720  type(g_tracer_type), pointer :: g_tracer, g_tracer_next
721  real, dimension(:,:,:,:), pointer :: tr_field
722  real, dimension(:,:,:), pointer :: tr_ptr
723  character(len=fm_string_len), parameter :: sub_name = 'MOM_generic_tracer_stock'
724 
725  integer :: i, j, k, is, ie, js, je, nz, m
726  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
727 
728  mom_generic_tracer_stock = 0
729  if (.not.associated(cs)) return
730 
731  if (present(stock_index)) then ; if (stock_index > 0) then
732  ! Check whether this stock is available from this routine.
733 
734  ! No stocks from this routine are being checked yet. Return 0.
735  return
736  endif ; endif
737 
738  if(.NOT. associated(cs%g_tracer_list)) return ! No stocks.
739 
740  m=1 ; g_tracer=>cs%g_tracer_list
741  do
742  call g_tracer_get_alias(g_tracer,names(m))
743  call g_tracer_get_values(g_tracer,names(m),'units',units(m))
744  units(m) = trim(units(m))//" kg"
745  call g_tracer_get_pointer(g_tracer,names(m),'field',tr_field)
746 
747  stocks(m) = 0.0
748  tr_ptr => tr_field(:,:,:,1)
749  do k=1,nz ; do j=js,je ; do i=is,ie
750  stocks(m) = stocks(m) + tr_ptr(i,j,k) * &
751  (g%mask2dT(i,j) * g%areaT(i,j) * h(i,j,k))
752  enddo ; enddo ; enddo
753  stocks(m) = gv%H_to_kg_m2 * stocks(m)
754 
755  !traverse the linked list till hit NULL
756  call g_tracer_get_next(g_tracer, g_tracer_next)
757  if(.NOT. associated(g_tracer_next)) exit
758  g_tracer=>g_tracer_next
759  m = m+1
760  enddo
761 
762  mom_generic_tracer_stock = m
763 
764  end function mom_generic_tracer_stock
765 
766  ! <SUBROUTINE NAME="MOM_generic_tracer_min_max">
767  ! <OVERVIEW>
768  ! Find the min and max of tracer concentrations.
769  ! </OVERVIEW>
770  ! <DESCRIPTION>
771  ! This subroutine find the global min and max of either
772  ! of all available tracer concentrations, or of a tracer that is
773  ! being requested specifically, returning the number of tracers it has gone through.
774  ! </DESCRIPTION>
775  ! <TEMPLATE>
776  ! ns = MOM_generic_tracer_min_max(do_minmax, gmin, gmax, igmin, jgmin, kgmin, igmax, jgmax, kgmax , G, CS, names, units)
777  ! </TEMPLATE>
778  ! </SUBROUTINE>
779 
780  function mom_generic_tracer_min_max(ind_start, got_minmax, gmin, gmax, xgmin, ygmin, zgmin, xgmax, ygmax, zgmax , G, CS, names, units)
781  use mpp_utilities_mod, only: mpp_array_global_min_max
782  integer, intent(in) :: ind_start
783  logical, dimension(:), intent(out) :: got_minmax
784  real, dimension(:), intent(out) :: gmin,gmax
785  real, dimension(:), intent(out) :: xgmin, ygmin, zgmin, xgmax, ygmax, zgmax
786  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
787  type(mom_generic_tracer_cs), pointer :: cs
788  character(len=*), dimension(:), intent(out) :: names
789  character(len=*), dimension(:), intent(out) :: units
790  integer :: mom_generic_tracer_min_max
791  ! This function calculates the mass-weighted integral of all tracer stocks,
792  ! returning the number of stocks it has calculated. If the stock_index
793  ! is present, only the stock corresponding to that coded index is returned.
794 
795  ! Arguments: h - Layer thickness, in m or kg m-2.
796  ! (out) gmin , gmax - the global minimum and maximum of each tracer,
797  ! in kg times concentration units.
798  ! (in) G - The ocean's grid structure.
799  ! (in) CS - The control structure returned by a previous call to
800  ! register_MOM_generic_tracer.
801  ! (out) names - the names of the stocks calculated.
802  ! (out) units - the units of the stocks calculated.
803  ! (in,opt) trace_index - the coded index of a specific tracer being sought.
804  ! Return value: the number of tracers done here.
805 
806  type(g_tracer_type), pointer :: g_tracer, g_tracer_next
807  real, dimension(:,:,:,:), pointer :: tr_field
808  real, dimension(:,:,:), pointer :: tr_ptr
809  character(len=fm_string_len), parameter :: sub_name = 'MOM_generic_tracer_min_max'
810 
811  real, dimension(:,:,:),pointer :: grid_tmask
812  integer :: isc,iec,jsc,jec,isd,ied,jsd,jed,nk,ntau
813 
814  integer :: i, j, k, is, ie, js, je, nz, m
815  real, allocatable, dimension(:) :: geo_z
816 
817  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
818 
819  mom_generic_tracer_min_max = 0
820  if (.not.associated(cs)) return
821 
822  if(.NOT. associated(cs%g_tracer_list)) return ! No stocks.
823 
824 
825  call g_tracer_get_common(isc,iec,jsc,jec,isd,ied,jsd,jed,nk,ntau,grid_tmask=grid_tmask)
826 
827  ! Because the use of a simple z-coordinate can not be assumed, simply
828  ! use the layer index as the vertical label.
829  allocate(geo_z(nk))
830  do k=1,nk ; geo_z(k) = real(k) ; enddo
831 
832 
833  m=ind_start ; g_tracer=>cs%g_tracer_list
834  do
835  call g_tracer_get_alias(g_tracer,names(m))
836  call g_tracer_get_values(g_tracer,names(m),'units',units(m))
837  units(m) = trim(units(m))//" kg"
838  call g_tracer_get_pointer(g_tracer,names(m),'field',tr_field)
839 
840  gmin(m) = -1.0
841  gmax(m) = -1.0
842 
843  tr_ptr => tr_field(:,:,:,1)
844 
845 
846  call mpp_array_global_min_max(tr_ptr, grid_tmask,isd,jsd,isc,iec,jsc,jec,nk , gmin(m), gmax(m), &
847  g%geoLonT,g%geoLatT,geo_z,xgmin(m), ygmin(m), zgmin(m), xgmax(m), ygmax(m), zgmax(m))
848 
849  got_minmax(m) = .true.
850 
851 
852  !traverse the linked list till hit NULL
853  call g_tracer_get_next(g_tracer, g_tracer_next)
854  if(.NOT. associated(g_tracer_next)) exit
855  g_tracer=>g_tracer_next
856  m = m+1
857  enddo
858 
859  mom_generic_tracer_min_max = m
860 
861  end function mom_generic_tracer_min_max
862 
863 
864  ! <SUBROUTINE NAME="MOM_generic_tracer_surface_state">
865  ! <OVERVIEW>
866  ! Calculate the surface state and set coupler values
867  ! </OVERVIEW>
868  ! <DESCRIPTION>
869  ! This subroutine calculates the surface state and set coupler values for
870  ! those generic tracers that havd flux exchange with atmosphere.
871  ! </DESCRIPTION>
872  ! <TEMPLATE>
873  ! call MOM_generic_tracer_surface_state(state, h, G, CS)
874  ! </TEMPLATE>
875  ! </SUBROUTINE>
876 
877  subroutine mom_generic_tracer_surface_state(state, h, G, CS)
878  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
879  type(surface), intent(inout) :: state
880  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
881  type(mom_generic_tracer_cs), pointer :: cs
882  ! This subroutine sets up the fields that the coupler needs to calculate the
883  ! CFC fluxes between the ocean and atmosphere.
884  ! Arguments: state - A structure containing fields that describe the
885  ! surface state of the ocean.
886  ! (in) h - Layer thickness, in m.
887  ! (in) G - The ocean's grid structure.
888  ! (in) CS - The control structure returned by a previous call to
889  ! register_MOM_generic_tracer.
890 
891  real :: sosga
892 
893  character(len=fm_string_len), parameter :: sub_name = 'MOM_generic_tracer_surface_state'
894  real, dimension(G%isd:G%ied,G%jsd:G%jed,1:G%ke,1) :: rho0
895  real, dimension(G%isd:G%ied,G%jsd:G%jed,1:G%ke) :: dzt
896  type(g_tracer_type), pointer :: g_tracer
897 
898  !Set coupler values
899  !nnz: fake rho0
900  rho0=1.0
901 
902  dzt(:,:,:) = cs%H_to_m * h(:,:,:)
903 
904  sosga = global_area_mean(state%SSS, g)
905 
906  call generic_tracer_coupler_set(state%tr_fields,&
907  st=state%SST,&
908  ss=state%SSS,&
909  rho=rho0,& !nnz: required for MOM5 and previous versions.
910  ilb=g%isd, jlb=g%jsd,&
911  dzt=dzt,& !This is needed for the Mocsy method of carbonate system vars
912  tau=1,sosga=sosga,model_time=get_diag_time_end(cs%diag))
913 
914  !Output diagnostics via diag_manager for all tracers in this module
915 ! if(.NOT. associated(CS%g_tracer_list)) call mpp_error(FATAL, trim(sub_name)//&
916 ! "No tracer in the list.")
917 ! call g_tracer_send_diag(CS%g_tracer_list, get_diag_time_end(CS%diag), tau=1)
918  !Niki: The problem with calling diagnostic outputs here is that this subroutine is called every dt_cpld
919  ! hence if dt_therm > dt_cpld we get output (and contribution to the mean) at times that tracers
920  ! had not been updated.
921  ! Moving this to the end of column physics subrotuine fixes this issue.
922 
923  end subroutine mom_generic_tracer_surface_state
924 
925 !ALL PE subroutine on Ocean! Due to otpm design the fluxes should be initialized like this on ALL PE's!
926  subroutine mom_generic_flux_init
927 
928  integer :: ind
929  character(len=fm_string_len) :: g_tracer_name,longname, package,units,old_package,file_in,file_out
930  real :: const_init_value
931  character(len=fm_string_len), parameter :: sub_name = 'MOM_generic_flux_init'
932  type(g_tracer_type), pointer :: g_tracer_list,g_tracer,g_tracer_next
933 
934  if (.not. g_registered) then
935  call generic_tracer_register
936  g_registered = .true.
937  endif
938 
939  call generic_tracer_get_list(g_tracer_list)
940  if(.NOT. associated(g_tracer_list)) then
941  call mpp_error(warning, trim(sub_name)// ": No generic tracer in the list.")
942  return
943  endif
944 
945  g_tracer=>g_tracer_list
946  do
947 
948  call g_tracer_flux_init(g_tracer)
949 
950  !traverse the linked list till hit NULL
951  call g_tracer_get_next(g_tracer, g_tracer_next)
952  if(.NOT. associated(g_tracer_next)) exit
953  g_tracer=>g_tracer_next
954 
955  enddo
956 
957  end subroutine mom_generic_flux_init
958 
959  subroutine mom_generic_tracer_fluxes_accumulate(flux_tmp, weight)
960  type(forcing), intent(in) :: flux_tmp
961  real, intent(in) :: weight
962 
963  call generic_tracer_coupler_accumulate(flux_tmp%tr_fluxes, weight)
964 
965  end subroutine mom_generic_tracer_fluxes_accumulate
966 
967  subroutine mom_generic_tracer_get(name,member,array, CS)
968  character(len=*), intent(in) :: name
969  character(len=*), intent(in) :: member
970  real, dimension(:,:,:), intent(out) :: array
971  type(mom_generic_tracer_cs), pointer :: cs
972  ! (in) CS - The control structure returned by a previous call to
973  ! register_MOM_generic_tracer.
974 
975  real, dimension(:,:,:), pointer :: array_ptr
976  character(len=fm_string_len), parameter :: sub_name = 'MOM_generic_tracer_get'
977 
978  call g_tracer_get_pointer(cs%g_tracer_list,name,member,array_ptr)
979  array(:,:,:) = array_ptr(:,:,:)
980 
981  end subroutine mom_generic_tracer_get
982 
983  ! <SUBROUTINE NAME="end_MOM_generic_tracer">
984  ! <OVERVIEW>
985  ! Ends the generic tracer module
986  ! </OVERVIEW>
987  ! <DESCRIPTION>
988  ! Call the end for generic tracer module and deallocate all temp arrays
989  ! </DESCRIPTION>
990  ! <TEMPLATE>
991  ! call end_MOM_generic_tracer(CS)
992  ! </TEMPLATE>
993  ! </SUBROUTINE>
994 
995  subroutine end_mom_generic_tracer(CS)
996  type(mom_generic_tracer_cs), pointer :: cs
997  ! This subroutine deallocates the memory owned by this module.
998  ! Argument: CS - The control structure returned by a previous call to
999  ! register_MOM_generic_tracer.
1000  integer :: m
1001 
1002  call generic_tracer_end
1003 
1004  if (associated(cs)) then
1005  deallocate(cs)
1006  endif
1007  end subroutine end_mom_generic_tracer
1008 
1009 #endif /* _USE_GENERIC_TRACER */
1010 end module mom_generic_tracer
The following structure contains pointers to various fields which may be used describe the surface st...
type(vardesc) function, public var_desc(name, units, longname, hor_grid, z_grid, t_grid, cmor_field_name, cmor_units, conversion, caller)
Returns a vardesc type whose elements have been filled with the provided fields. The argument name is...
Definition: MOM_io.F90:585
This module implements boundary forcing for MOM6.
logical function, public tracer_z_init(tr, h, filename, tr_name, G, missing_val, land_val)
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...
Provides the ocean grid type.
Definition: MOM_grid.F90:2
This module contains I/O framework code.
Definition: MOM_io.F90:2
Defines the horizontal index type (hor_index_type) used for providing index ranges.
subroutine, public set_up_ale_sponge_field(sp_val, G, f_ptr, CS)
This subroutine stores the reference profile at h points for the variable.
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)
SPONGE control structure.
Container for horizontal index ranges for data, computational and global domains. ...
subroutine, public register_tracer(tr1, tr_desc, param_file, HI, GV, Reg, tr_desc_ptr, ad_x, ad_y, df_x, df_y, OBC_inflow, OBC_in_u, OBC_in_v, ad_2d_x, ad_2d_y, df_2d_x, df_2d_y, advection_xy)
This subroutine registers a tracer to be advected and laterally diffused.
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
subroutine, public applytracerboundaryfluxesinout(G, GV, Tr, dt, fluxes, h, evap_CFL_limit, minimum_forcing_depth, in_flux_optional, out_flux_optional, update_h_opt)
This routine is modeled after applyBoundaryFluxesInOut in MOM_diabatic_aux.F90 NOTE: Please note that...
subroutine, public set_up_sponge_field(sp_val, f_ptr, G, nlay, CS, sp_val_i_mean)
Definition: MOM_sponge.F90:271
Type to carry basic tracer information.
logical function, public is_root_pe()
This module contains routines that implement physical fluxes of tracers (e.g. due to surface fluxes o...
subroutine, public register_z_tracer(tr_ptr, name, long_name, units, Time, G, CS, standard_name, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name)
This subroutine registers a tracer to be output in depth space.
subroutine, public add_tracer_obc_values(name, Reg, OBC_inflow, OBC_in_u, OBC_in_v)
This subroutine adds open boundary condition concentrations for a tracer that has previously been reg...
subroutine, public add_tracer_diagnostics(name, Reg, ad_x, ad_y, df_x, df_y, ad_2d_x, ad_2d_y, df_2d_x, df_2d_y, advection_xy)
This subroutine adds diagnostic arrays for a tracer that has previously been registered by a call to ...
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
Type for describing a variable, typically a tracer.
Definition: MOM_io.F90:51
subroutine, public tracer_vertdiff(h_old, ea, eb, dt, tr, G, GV, sfc_flux, btm_flux, btm_reservoir, sink_rate, convert_flux_in)
This subroutine solves a tridiagonal equation for the final tracer concentrations after the dual-entr...
type(time_type) function, public get_diag_time_end(diag_cs)
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
Controls where open boundary conditions are applied.
real function, public global_area_mean(var, G)
integer function, public register_diag_field(module_name, field_name, axes, init_time, long_name, units, missing_value, range, mask_variant, standard_name, verbose, do_not_log, err_msg, interp_method, tile_count, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name, cell_methods, x_cell_method, y_cell_method, v_cell_method, conversion, v_extensive)
Returns the "diag_mediator" handle for a group (native, CMOR, z-coord, ...) of diagnostics derived fr...
subroutine, public mom_error(level, message, all_print)