MOM6
isomip_tracer Module Reference

Detailed Description

Routines used to set up and use a set of (one for now) dynamically passive tracers in the ISOMIP configuration.

For now, just one passive tracer is injected in the sponge layer.

Data Types

type  isomip_tracer_cs
 ISOMIP tracer package control structure. More...
 

Functions/Subroutines

logical function, public register_isomip_tracer (HI, GV, param_file, CS, tr_Reg, restart_CS)
 This subroutine is used to register tracer fields. More...
 
subroutine, public initialize_isomip_tracer (restart, day, G, GV, h, diag, OBC, CS, ALE_sponge_CSp)
 Initializes the NTR tracer fields in tr(:,:,:,:) More...
 
subroutine, public isomip_tracer_column_physics (h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, evap_CFL_limit, minimum_forcing_depth)
 This subroutine applies diapycnal diffusion, including the surface boundary conditions and any other column tracer physics or chemistry to the tracers from this file. More...
 
subroutine, public isomip_tracer_surface_state (state, h, G, CS)
 This subroutine extracts the surface fields from this tracer package that are to be shared with the atmosphere in coupled configurations. This particular tracer package does not report anything back to the coupler. More...
 
subroutine, public isomip_tracer_end (CS)
 Deallocate any memory used by the ISOMIP tracer package. More...
 

Variables

integer, parameter ntr = 1
 ntr is the number of tracers in this module.
 

Function/Subroutine Documentation

◆ initialize_isomip_tracer()

subroutine, public isomip_tracer::initialize_isomip_tracer ( logical, intent(in)  restart,
type(time_type), intent(in), target  day,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(in)  h,
type(diag_ctrl), intent(in), target  diag,
type(ocean_obc_type), pointer  OBC,
type(isomip_tracer_cs), pointer  CS,
type(ale_sponge_cs), pointer  ALE_sponge_CSp 
)

Initializes the NTR tracer fields in tr(:,:,:,:)

Parameters
[in]gGrid structure.
[in]gvThe ocean's vertical grid structure.
[in]restart.true. if the fields have already been read from a restart file.
[in]dayTime of the start of the run.
[in]hLayer thickness [H ~> m or kg m-2].
[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. This is not being used for now.
csThe control structure returned by a previous call to ISOMIP_register_tracer.
ale_sponge_cspA pointer to the control structure for the sponges, if they are in use. Otherwise this may be unassociated.

Definition at line 149 of file ISOMIP_tracer.F90.

149 
150  type(ocean_grid_type), intent(in) :: G !< Grid structure.
151  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
152  logical, intent(in) :: restart !< .true. if the fields have already
153  !! been read from a restart file.
154  type(time_type), target, intent(in) :: day !< Time of the start of the run.
155  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thickness [H ~> m or kg m-2].
156  type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to regulate
157  !! diagnostic output.
158  type(ocean_OBC_type), pointer :: OBC !< This open boundary condition type specifies
159  !! whether, where, and what open boundary conditions
160  !! are used. This is not being used for now.
161  type(ISOMIP_tracer_CS), pointer :: CS !< The control structure returned by a previous call
162  !! to ISOMIP_register_tracer.
163  type(ALE_sponge_CS), pointer :: ALE_sponge_CSp !< A pointer to the control structure for
164  !! the sponges, if they are in use. Otherwise this
165  !! may be unassociated.
166 
167  real, allocatable :: temp(:,:,:)
168  real, pointer, dimension(:,:,:) :: &
169  OBC_tr1_u => null(), & ! These arrays should be allocated and set to
170  obc_tr1_v => null() ! specify the values of tracer 1 that should come
171  ! in through u- and v- points through the open
172  ! boundary conditions, in the same units as tr.
173  character(len=16) :: name ! A variable's name in a NetCDF file.
174  character(len=72) :: longname ! The long name of that variable.
175  character(len=48) :: units ! The dimensions of the variable.
176  character(len=48) :: flux_units ! The units for tracer fluxes, usually
177  ! kg(tracer) kg(water)-1 m3 s-1 or kg(tracer) s-1.
178  real, pointer :: tr_ptr(:,:,:) => null()
179  real :: PI ! 3.1415926... calculated as 4*atan(1)
180  real :: tr_y ! Initial zonally uniform tracer concentrations.
181  real :: dist2 ! The distance squared from a line [m2].
182  real :: h_neglect ! A thickness that is so small it is usually lost
183  ! in roundoff and can be neglected [H ~> m or kg m-2].
184  real :: e(SZK_(G)+1), e_top, e_bot, d_tr
185  integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz, m
186  integer :: IsdB, IedB, JsdB, JedB
187 
188  if (.not.associated(cs)) return
189  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
190  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
191  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
192  h_neglect = gv%H_subroundoff
193 
194  cs%Time => day
195  cs%diag => diag
196 
197  if (.not.restart) then
198  if (len_trim(cs%tracer_IC_file) >= 1) then
199  ! Read the tracer concentrations from a netcdf file.
200  if (.not.file_exists(cs%tracer_IC_file, g%Domain)) &
201  call mom_error(fatal, "ISOMIP_initialize_tracer: Unable to open "// &
202  cs%tracer_IC_file)
203  do m=1,ntr
204  call query_vardesc(cs%tr_desc(m), name, caller="initialize_ISOMIP_tracer")
205  call mom_read_data(cs%tracer_IC_file, trim(name), cs%tr(:,:,:,m), g%Domain)
206  enddo
207  else
208  do m=1,ntr
209  do k=1,nz ; do j=js,je ; do i=is,ie
210  cs%tr(i,j,k,m) = 0.0
211  enddo ; enddo ; enddo
212  enddo
213  endif
214  endif ! restart
215 
216 ! the following does not work in layer mode yet
217 !! if ( CS%use_sponge ) then
218  ! If sponges are used, this example damps tracers in sponges in the
219  ! northern half of the domain to 1 and tracers in the southern half
220  ! to 0. For any tracers that are not damped in the sponge, the call
221  ! to set_up_sponge_field can simply be omitted.
222 ! if (.not.associated(ALE_sponge_CSp)) &
223 ! call MOM_error(FATAL, "ISOMIP_initialize_tracer: "// &
224 ! "The pointer to ALEsponge_CSp must be associated if SPONGE is defined.")
225 
226 ! allocate(temp(G%isd:G%ied,G%jsd:G%jed,nz))
227 
228 ! do j=js,je ; do i=is,ie
229 ! if (G%geoLonT(i,j) >= 790.0 .AND. G%geoLonT(i,j) <= 800.0) then
230 ! temp(i,j,:) = 1.0
231 ! else
232 ! temp(i,j,:) = 0.0
233 ! endif
234 ! enddo ; enddo
235 
236  ! do m=1,NTR
237 ! do m=1,1
238  ! This is needed to force the compiler not to do a copy in the sponge
239  ! calls. Curses on the designers and implementers of Fortran90.
240 ! tr_ptr => CS%tr(:,:,:,m)
241 ! call set_up_ALE_sponge_field(temp, G, tr_ptr, ALE_sponge_CSp)
242 ! enddo
243 ! deallocate(temp)
244 ! endif
245 

◆ isomip_tracer_column_physics()

subroutine, public isomip_tracer::isomip_tracer_column_physics ( real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  h_old,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  h_new,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  ea,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  eb,
type(forcing), intent(in)  fluxes,
real, intent(in)  dt,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(isomip_tracer_cs), pointer  CS,
real, intent(in), optional  evap_CFL_limit,
real, intent(in), optional  minimum_forcing_depth 
)

This subroutine applies diapycnal diffusion, including the surface boundary conditions and any other column tracer physics or chemistry to the tracers from this file.

Parameters
[in]gThe ocean's grid structure
[in]gvThe ocean's vertical grid structure
[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
[in]eban array to which the amount of fluid entrained
[in]fluxesA structure containing pointers to thermodynamic and tracer forcing fields. Unused fields have NULL ptrs.
[in]dtThe amount of time covered by this call [s]
csThe control structure returned by a previous call to ISOMIP_register_tracer.
[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 [m]

Definition at line 252 of file ISOMIP_tracer.F90.

252  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
253  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
254  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
255  intent(in) :: h_old !< Layer thickness before entrainment [H ~> m or kg m-2].
256  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
257  intent(in) :: h_new !< Layer thickness after entrainment [H ~> m or kg m-2].
258  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
259  intent(in) :: ea !< an array to which the amount of fluid entrained
260  !! from the layer above during this call will be
261  !! added [H ~> m or kg m-2].
262  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
263  intent(in) :: eb !< an array to which the amount of fluid entrained
264  !! from the layer below during this call will be
265  !! added [H ~> m or kg m-2].
266  type(forcing), intent(in) :: fluxes !< A structure containing pointers to thermodynamic
267  !! and tracer forcing fields. Unused fields have NULL ptrs.
268  real, intent(in) :: dt !< The amount of time covered by this call [s]
269  type(ISOMIP_tracer_CS), pointer :: CS !< The control structure returned by a previous
270  !! call to ISOMIP_register_tracer.
271  real, optional, intent(in) :: evap_CFL_limit !< Limit on the fraction of the water that can
272  !! be fluxed out of the top layer in a timestep [nondim]
273  real, optional, intent(in) :: minimum_forcing_depth !< The smallest depth over which
274  !! fluxes can be applied [m]
275 
276 ! The arguments to this subroutine are redundant in that
277 ! h_new(k) = h_old(k) + ea(k) - eb(k-1) + eb(k) - ea(k+1)
278 
279  ! Local variables
280  real :: mmax
281  real :: b1(SZI_(G)) ! b1 and c1 are variables used by the
282  real :: c1(SZI_(G),SZK_(G)) ! tridiagonal solver.
283  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_work ! Used so that h can be modified
284  real :: melt(SZI_(G),SZJ_(G)) ! melt water (positive for melting
285  ! negative for freezing)
286  character(len=256) :: mesg ! The text of an error message
287  integer :: i, j, k, is, ie, js, je, nz, m
288  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
289 
290  if (.not.associated(cs)) return
291 
292  melt(:,:) = fluxes%iceshelf_melt
293 
294  ! max. melt
295  mmax = maxval(melt(is:ie,js:je))
296  call max_across_pes(mmax)
297  ! write(mesg,*) 'max melt = ', mmax
298  ! call MOM_mesg(mesg, 5)
299  ! dye melt water (m=1), dye = 1 if melt=max(melt)
300  do m=1,ntr
301  do j=js,je ; do i=is,ie
302  if (melt(i,j) > 0.0) then ! melting
303  cs%tr(i,j,1:2,m) = melt(i,j)/mmax ! inject dye in the ML
304  else ! freezing
305  cs%tr(i,j,1:2,m) = 0.0
306  endif
307  enddo ; enddo
308  enddo
309 
310  if (present(evap_cfl_limit) .and. present(minimum_forcing_depth)) then
311  do m=1,ntr
312  do k=1,nz ;do j=js,je ; do i=is,ie
313  h_work(i,j,k) = h_old(i,j,k)
314  enddo ; enddo ; enddo
315  call applytracerboundaryfluxesinout(g, gv, cs%tr(:,:,:,m) , dt, fluxes, h_work, &
316  evap_cfl_limit, minimum_forcing_depth)
317  call tracer_vertdiff(h_work, ea, eb, dt, cs%tr(:,:,:,m), g, gv)
318  enddo
319  else
320  do m=1,ntr
321  call tracer_vertdiff(h_old, ea, eb, dt, cs%tr(:,:,:,m), g, gv)
322  enddo
323  endif
324 

◆ isomip_tracer_end()

subroutine, public isomip_tracer::isomip_tracer_end ( type(isomip_tracer_cs), pointer  CS)

Deallocate any memory used by the ISOMIP tracer package.

Parameters
csThe control structure returned by a previous call to ISOMIP_register_tracer.

Definition at line 362 of file ISOMIP_tracer.F90.

362  type(ISOMIP_tracer_CS), pointer :: CS !< The control structure returned by a previous
363  !! call to ISOMIP_register_tracer.
364  integer :: m
365 
366  if (associated(cs)) then
367  if (associated(cs%tr)) deallocate(cs%tr)
368  deallocate(cs)
369  endif

◆ isomip_tracer_surface_state()

subroutine, public isomip_tracer::isomip_tracer_surface_state ( type(surface), intent(inout)  state,
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(in)  h,
type(ocean_grid_type), intent(in)  G,
type(isomip_tracer_cs), pointer  CS 
)

This subroutine extracts the surface fields from this tracer package that are to be shared with the atmosphere in coupled configurations. This particular tracer package does not report anything back to the coupler.

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

Definition at line 331 of file ISOMIP_tracer.F90.

331  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
332  type(surface), intent(inout) :: state !< A structure containing fields that
333  !! describe the surface state of the ocean.
334  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
335  intent(in) :: h !< Layer thickness [H ~> m or kg m-2].
336  type(ISOMIP_tracer_CS), pointer :: CS !< The control structure returned by a previous
337  !! call to ISOMIP_register_tracer.
338 
339  ! This particular tracer package does not report anything back to the coupler.
340  ! The code that is here is just a rough guide for packages that would.
341 
342  integer :: m, is, ie, js, je, isd, ied, jsd, jed
343  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
344  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
345 
346  if (.not.associated(cs)) return
347 
348  if (cs%coupled_tracers) then
349  do m=1,ntr
350  ! This call loads the surface values into the appropriate array in the
351  ! coupler-type structure.
352  call coupler_type_set_data(cs%tr(:,:,1,m), cs%ind_tr(m), ind_csurf, &
353  state%tr_fields, idim=(/isd, is, ie, ied/), &
354  jdim=(/jsd, js, je, jed/) )
355  enddo
356  endif
357 

◆ register_isomip_tracer()

logical function, public isomip_tracer::register_isomip_tracer ( type(hor_index_type), intent(in)  HI,
type(verticalgrid_type), intent(in)  GV,
type(param_file_type), intent(in)  param_file,
type(isomip_tracer_cs), pointer  CS,
type(tracer_registry_type), pointer  tr_Reg,
type(mom_restart_cs), pointer  restart_CS 
)

This subroutine is used to register tracer fields.

Parameters
[in]hiA horizontal index type structure.
[in]gvThe ocean's vertical grid structure.
[in]param_fileA structure indicating the open file to parse for model parameter values.
csA pointer that is set to point to the control structure for this module (in/out).
tr_regA pointer to the tracer registry.
restart_csA pointer to the restart control structure.

Definition at line 68 of file ISOMIP_tracer.F90.

68  type(hor_index_type), intent(in) :: HI !<A horizontal index type structure.
69  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
70  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
71  !! to parse for model parameter values.
72  type(ISOMIP_tracer_CS), pointer :: CS !<A pointer that is set to point to the control
73  !! structure for this module (in/out).
74  type(tracer_registry_type), pointer :: tr_Reg !<A pointer to the tracer registry.
75  type(MOM_restart_CS), pointer :: restart_CS !<A pointer to the restart control structure.
76 
77  character(len=80) :: name, longname
78 ! This include declares and sets the variable "version".
79 #include "version_variable.h"
80  character(len=40) :: mdl = "ISOMIP_tracer" ! This module's name.
81  character(len=200) :: inputdir
82  character(len=48) :: flux_units ! The units for tracer fluxes, usually
83  ! kg(tracer) kg(water)-1 m3 s-1 or kg(tracer) s-1.
84  real, pointer :: tr_ptr(:,:,:) => null()
85  logical :: register_ISOMIP_tracer
86  integer :: isd, ied, jsd, jed, nz, m
87  isd = hi%isd ; ied = hi%ied ; jsd = hi%jsd ; jed = hi%jed ; nz = gv%ke
88 
89  if (associated(cs)) then
90  call mom_error(warning, "ISOMIP_register_tracer called with an "// &
91  "associated control structure.")
92  return
93  endif
94  allocate(cs)
95 
96  ! Read all relevant parameters and write them to the model log.
97  call log_version(param_file, mdl, version, "")
98  call get_param(param_file, mdl, "ISOMIP_TRACER_IC_FILE", cs%tracer_IC_file, &
99  "The name of a file from which to read the initial "//&
100  "conditions for the ISOMIP tracers, or blank to initialize "//&
101  "them internally.", default=" ")
102  if (len_trim(cs%tracer_IC_file) >= 1) then
103  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
104  inputdir = slasher(inputdir)
105  cs%tracer_IC_file = trim(inputdir)//trim(cs%tracer_IC_file)
106  call log_param(param_file, mdl, "INPUTDIR/ISOMIP_TRACER_IC_FILE", &
107  cs%tracer_IC_file)
108  endif
109  call get_param(param_file, mdl, "SPONGE", cs%use_sponge, &
110  "If true, sponges may be applied anywhere in the domain. "//&
111  "The exact location and properties of those sponges are "//&
112  "specified from MOM_initialization.F90.", default=.false.)
113 
114  allocate(cs%tr(isd:ied,jsd:jed,nz,ntr)) ; cs%tr(:,:,:,:) = 0.0
115 
116  do m=1,ntr
117  if (m < 10) then ; write(name,'("tr_D",I1.1)') m
118  else ; write(name,'("tr_D",I2.2)') m ; endif
119  write(longname,'("Concentration of ISOMIP Tracer ",I2.2)') m
120  cs%tr_desc(m) = var_desc(name, units="kg kg-1", longname=longname, caller=mdl)
121  if (gv%Boussinesq) then ; flux_units = "kg kg-1 m3 s-1"
122  else ; flux_units = "kg s-1" ; endif
123 
124  ! This is needed to force the compiler not to do a copy in the registration
125  ! calls. Curses on the designers and implementers of Fortran90.
126  tr_ptr => cs%tr(:,:,:,m)
127  ! Register the tracer for horizontal advection, diffusion, and restarts.
128  call register_tracer(tr_ptr, tr_reg, param_file, hi, gv, &
129  name=name, longname=longname, units="kg kg-1", &
130  registry_diags=.true., flux_units=flux_units, &
131  restart_cs=restart_cs)
132 
133  ! Set coupled_tracers to be true (hard-coded above) to provide the surface
134  ! values to the coupler (if any). This is meta-code and its arguments will
135  ! currently (deliberately) give fatal errors if it is used.
136  if (cs%coupled_tracers) &
137  cs%ind_tr(m) = aof_set_coupler_flux(trim(name)//'_flux', &
138  flux_type=' ', implementation=' ', caller="register_ISOMIP_tracer")
139  enddo
140 
141  cs%tr_Reg => tr_reg
142  register_isomip_tracer = .true.