MOM6
oil_tracer.F90
1 !> A tracer package to mimic dissolved oil.
2 module oil_tracer
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
7 use mom_error_handler, only : mom_error, fatal, warning
9 use mom_forcing_type, only : forcing
10 use mom_grid, only : ocean_grid_type
11 use mom_hor_index, only : hor_index_type
12 use mom_io, only : file_exists, mom_read_data, slasher, vardesc, var_desc, query_vardesc
15 use mom_sponge, only : set_up_sponge_field, sponge_cs
16 use mom_time_manager, only : time_type, time_type_to_real
17 use mom_tracer_registry, only : register_tracer, tracer_registry_type
18 use mom_tracer_diabatic, only : tracer_vertdiff, applytracerboundaryfluxesinout
19 use mom_tracer_z_init, only : tracer_z_init
23 
24 use coupler_types_mod, only : coupler_type_set_data, ind_csurf
25 use atmos_ocean_fluxes_mod, only : aof_set_coupler_flux
26 
27 implicit none ; private
28 
29 #include <MOM_memory.h>
30 
31 public register_oil_tracer, initialize_oil_tracer
32 public oil_tracer_column_physics, oil_tracer_surface_state
33 public oil_stock, oil_tracer_end
34 
35 integer, parameter :: ntr_max = 20 !< the maximum number of tracers in this module.
36 
37 !> The control structure for the oil tracer package
38 type, public :: oil_tracer_cs ; private
39  integer :: ntr !< The number of tracers that are actually used.
40  logical :: coupled_tracers = .false. !< These tracers are not offered to the coupler.
41  character(len=200) :: ic_file !< The file in which the age-tracer initial values
42  !! can be found, or an empty string for internal initialization.
43  logical :: z_ic_file !< If true, the IC_file is in Z-space. The default is false.
44  real :: oil_source_longitude !< Latitude of source location (geographic)
45  real :: oil_source_latitude !< Longitude of source location (geographic)
46  integer :: oil_source_i=-999 !< Local i of source location (computational)
47  integer :: oil_source_j=-999 !< Local j of source location (computational)
48  real :: oil_source_rate !< Rate of oil injection [kg s-1]
49  real :: oil_start_year !< The year in which tracers start aging, or at which the
50  !! surface value equals young_val, in years.
51  real :: oil_end_year !< The year in which tracers start aging, or at which the
52  !! surface value equals young_val, in years.
53  type(time_type), pointer :: time => null() !< A pointer to the ocean model's clock.
54  type(tracer_registry_type), pointer :: tr_reg => null() !< A pointer to the MOM tracer registry
55  real, pointer :: tr(:,:,:,:) => null() !< The array of tracers used in this subroutine, in g m-3?
56  real, dimension(NTR_MAX) :: ic_val = 0.0 !< The (uniform) initial condition value.
57  real, dimension(NTR_MAX) :: young_val = 0.0 !< The value assigned to tr at the surface.
58  real, dimension(NTR_MAX) :: land_val = -1.0 !< The value of tr used where land is masked out.
59  real, dimension(NTR_MAX) :: sfc_growth_rate !< The exponential growth rate for the surface value [year-1].
60  real, dimension(NTR_MAX) :: oil_decay_days !< Decay time scale of oil [days]
61  real, dimension(NTR_MAX) :: oil_decay_rate !< Decay rate of oil [s-1] calculated from oil_decay_days
62  integer, dimension(NTR_MAX) :: oil_source_k !< Layer of source
63  logical :: oil_may_reinit !< If true, oil tracers may be reset by the initialization code
64  !! if they are not found in the restart files.
65  integer, dimension(NTR_MAX) :: ind_tr !< Indices returned by aof_set_coupler_flux if it is used and the
66  !! surface tracer concentrations are to be provided to the coupler.
67  type(vardesc) :: tr_desc(ntr_max) !< Descriptions and metadata for the tracers
68 
69  type(diag_ctrl), pointer :: diag => null() !< A structure that is used to
70  !! regulate the timing of diagnostic output.
71  type(mom_restart_cs), pointer :: restart_csp => null() !< A pointer to the restart control structure
72 end type oil_tracer_cs
73 
74 contains
75 
76 !> Register oil tracer fields and subroutines to be used with MOM.
77 function register_oil_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
78  type(hor_index_type), intent(in) :: hi !< A horizontal index type structure
79  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
80  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
81  type(oil_tracer_cs), pointer :: cs !< A pointer that is set to point to the control
82  !! structure for this module
83  type(tracer_registry_type), pointer :: tr_reg !< A pointer that is set to point to the control
84  !! structure for the tracer advection and
85  !! diffusion module
86  type(mom_restart_cs), pointer :: restart_cs !< A pointer to the restart control structure
87 
88  ! Local variables
89  character(len=40) :: mdl = "oil_tracer" ! This module's name.
90 ! This include declares and sets the variable "version".
91 #include "version_variable.h"
92  character(len=200) :: inputdir ! The directory where the input files are.
93  character(len=48) :: var_name ! The variable's name.
94  character(len=3) :: name_tag ! String for creating identifying oils
95  character(len=48) :: flux_units ! The units for tracer fluxes, here
96  ! kg(oil) s-1 or kg(oil) m-3 kg(water) s-1.
97  real, pointer :: tr_ptr(:,:,:) => null()
98  logical :: register_oil_tracer
99  integer :: isd, ied, jsd, jed, nz, m, i, j
100  isd = hi%isd ; ied = hi%ied ; jsd = hi%jsd ; jed = hi%jed ; nz = gv%ke
101 
102  if (associated(cs)) then
103  call mom_error(warning, "register_oil_tracer called with an "// &
104  "associated control structure.")
105  return
106  endif
107  allocate(cs)
108 
109  ! Read all relevant parameters and write them to the model log.
110  call log_version(param_file, mdl, version, "")
111  call get_param(param_file, mdl, "OIL_IC_FILE", cs%IC_file, &
112  "The file in which the oil tracer initial values can be "//&
113  "found, or an empty string for internal initialization.", &
114  default=" ")
115  if ((len_trim(cs%IC_file) > 0) .and. (scan(cs%IC_file,'/') == 0)) then
116  ! Add the directory if CS%IC_file is not already a complete path.
117  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
118  cs%IC_file = trim(slasher(inputdir))//trim(cs%IC_file)
119  call log_param(param_file, mdl, "INPUTDIR/CFC_IC_FILE", cs%IC_file)
120  endif
121  call get_param(param_file, mdl, "OIL_IC_FILE_IS_Z", cs%Z_IC_file, &
122  "If true, OIL_IC_FILE is in depth space, not layer space", &
123  default=.false.)
124 
125  call get_param(param_file, mdl, "OIL_MAY_REINIT", cs%oil_may_reinit, &
126  "If true, oil tracers may go through the initialization "//&
127  "code if they are not found in the restart files. "//&
128  "Otherwise it is a fatal error if the oil tracers are not "//&
129  "found in the restart files of a restarted run.", &
130  default=.false.)
131  call get_param(param_file, mdl, "OIL_SOURCE_LONGITUDE", cs%oil_source_longitude, &
132  "The geographic longitude of the oil source.", units="degrees E", &
133  fail_if_missing=.true.)
134  call get_param(param_file, mdl, "OIL_SOURCE_LATITUDE", cs%oil_source_latitude, &
135  "The geographic latitude of the oil source.", units="degrees N", &
136  fail_if_missing=.true.)
137  call get_param(param_file, mdl, "OIL_SOURCE_LAYER", cs%oil_source_k, &
138  "The layer into which the oil is introduced, or a "//&
139  "negative number for a vertically uniform source, "//&
140  "or 0 not to use this tracer.", units="Layer", default=0)
141  call get_param(param_file, mdl, "OIL_SOURCE_RATE", cs%oil_source_rate, &
142  "The rate of oil injection.", units="kg s-1", default=1.0)
143  call get_param(param_file, mdl, "OIL_DECAY_DAYS", cs%oil_decay_days, &
144  "The decay timescale in days (if positive), or no decay "//&
145  "if 0, or use the temperature dependent decay rate of "//&
146  "Adcroft et al. (GRL, 2010) if negative.", units="days", &
147  default=0.0)
148  call get_param(param_file, mdl, "OIL_DATED_START_YEAR", cs%oil_start_year, &
149  "The time at which the oil source starts", units="years", &
150  default=0.0)
151  call get_param(param_file, mdl, "OIL_DATED_END_YEAR", cs%oil_end_year, &
152  "The time at which the oil source ends", units="years", &
153  default=1.0e99)
154 
155  cs%ntr = 0
156  cs%oil_decay_rate(:) = 0.
157  do m=1,ntr_max
158  if (cs%oil_source_k(m)/=0) then
159  write(name_tag(1:3),'("_",I2.2)') m
160  cs%ntr = cs%ntr + 1
161  cs%tr_desc(m) = var_desc("oil"//trim(name_tag), "kg m-3", "Oil Tracer", caller=mdl)
162  cs%IC_val(m) = 0.0
163  if (cs%oil_decay_days(m)>0.) then
164  cs%oil_decay_rate(m)=1./(86400.0*cs%oil_decay_days(m))
165  elseif (cs%oil_decay_days(m)<0.) then
166  cs%oil_decay_rate(m)=-1.
167  endif
168  endif
169  enddo
170  call log_param(param_file, mdl, "OIL_DECAY_RATE", cs%oil_decay_rate(1:cs%ntr))
171 
172  ! This needs to be changed if the units of tracer are changed above.
173  if (gv%Boussinesq) then ; flux_units = "kg s-1"
174  else ; flux_units = "kg m-3 kg s-1" ; endif
175 
176  allocate(cs%tr(isd:ied,jsd:jed,nz,cs%ntr)) ; cs%tr(:,:,:,:) = 0.0
177 
178  do m=1,cs%ntr
179  ! This is needed to force the compiler not to do a copy in the registration
180  ! calls. Curses on the designers and implementers of Fortran90.
181  tr_ptr => cs%tr(:,:,:,m)
182  call query_vardesc(cs%tr_desc(m), name=var_name, caller="register_oil_tracer")
183  ! Register the tracer for horizontal advection, diffusion, and restarts.
184  call register_tracer(tr_ptr, tr_reg, param_file, hi, gv, tr_desc=cs%tr_desc(m), &
185  registry_diags=.true., flux_units=flux_units, restart_cs=restart_cs, &
186  mandatory=.not.cs%oil_may_reinit)
187 
188  ! Set coupled_tracers to be true (hard-coded above) to provide the surface
189  ! values to the coupler (if any). This is meta-code and its arguments will
190  ! currently (deliberately) give fatal errors if it is used.
191  if (cs%coupled_tracers) &
192  cs%ind_tr(m) = aof_set_coupler_flux(trim(var_name)//'_flux', &
193  flux_type=' ', implementation=' ', caller="register_oil_tracer")
194  enddo
195 
196  cs%tr_Reg => tr_reg
197  cs%restart_CSp => restart_cs
198  register_oil_tracer = .true.
199 
200 end function register_oil_tracer
201 
202 !> Initialize the oil tracers and set up tracer output
203 subroutine initialize_oil_tracer(restart, day, G, GV, US, h, diag, OBC, CS, &
204  sponge_CSp)
205  logical, intent(in) :: restart !< .true. if the fields have already
206  !! been read from a restart file.
207  type(time_type), target, intent(in) :: day !< Time of the start of the run.
208  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
209  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
210  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
211  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
212  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
213  type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to regulate
214  !! diagnostic output.
215  type(ocean_obc_type), pointer :: obc !< This open boundary condition type specifies
216  !! whether, where, and what open boundary
217  !! conditions are used.
218  type(oil_tracer_cs), pointer :: cs !< The control structure returned by a previous
219  !! call to register_oil_tracer.
220  type(sponge_cs), pointer :: sponge_csp !< Pointer to the control structure for the sponges.
221 
222  ! Local variables
223  character(len=16) :: name ! A variable's name in a NetCDF file.
224  character(len=72) :: longname ! The long name of that variable.
225  character(len=48) :: units ! The dimensions of the variable.
226  character(len=48) :: flux_units ! The units for age tracer fluxes, either
227  ! years m3 s-1 or years kg s-1.
228  logical :: ok
229  integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz, m
230  integer :: isdb, iedb, jsdb, jedb
231 
232  if (.not.associated(cs)) return
233  if (cs%ntr < 1) return
234  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = gv%ke
235  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
236  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
237 
238  ! Establish location of source
239  do j=g%jsdB+1,g%jed ; do i=g%isdB+1,g%ied
240  ! This test for i,j index is specific to a lat/lon (non-rotated grid).
241  ! and needs to be generalized to work properly on the tri-polar grid.
242  if (cs%oil_source_longitude<g%geoLonBu(i,j) .and. &
243  cs%oil_source_longitude>=g%geoLonBu(i-1,j) .and. &
244  cs%oil_source_latitude<g%geoLatBu(i,j) .and. &
245  cs%oil_source_latitude>=g%geoLatBu(i,j-1) ) then
246  cs%oil_source_i=i
247  cs%oil_source_j=j
248  endif
249  enddo ; enddo
250 
251  cs%Time => day
252  cs%diag => diag
253 
254  do m=1,cs%ntr
255  call query_vardesc(cs%tr_desc(m), name=name, caller="initialize_oil_tracer")
256  if ((.not.restart) .or. (cs%oil_may_reinit .and. .not. &
257  query_initialized(cs%tr(:,:,:,m), name, cs%restart_CSp))) then
258 
259  if (len_trim(cs%IC_file) > 0) then
260  ! Read the tracer concentrations from a netcdf file.
261  if (.not.file_exists(cs%IC_file, g%Domain)) &
262  call mom_error(fatal, "initialize_oil_tracer: "// &
263  "Unable to open "//cs%IC_file)
264 
265  if (cs%Z_IC_file) then
266  ok = tracer_z_init(cs%tr(:,:,:,m), h, cs%IC_file, name, &
267  g, us, -1e34, 0.0) ! CS%land_val(m))
268  if (.not.ok) then
269  ok = tracer_z_init(cs%tr(:,:,:,m), h, cs%IC_file, &
270  trim(name), g, us, -1e34, 0.0) ! CS%land_val(m))
271  if (.not.ok) call mom_error(fatal,"initialize_oil_tracer: "//&
272  "Unable to read "//trim(name)//" from "//&
273  trim(cs%IC_file)//".")
274  endif
275  else
276  call mom_read_data(cs%IC_file, trim(name), cs%tr(:,:,:,m), g%Domain)
277  endif
278  else
279  do k=1,nz ; do j=js,je ; do i=is,ie
280  if (g%mask2dT(i,j) < 0.5) then
281  cs%tr(i,j,k,m) = cs%land_val(m)
282  else
283  cs%tr(i,j,k,m) = cs%IC_val(m)
284  endif
285  enddo ; enddo ; enddo
286  endif
287 
288  endif ! restart
289  enddo ! Tracer loop
290 
291  if (associated(obc)) then
292  ! Put something here...
293  endif
294 
295 end subroutine initialize_oil_tracer
296 
297 !> Apply sources, sinks, diapycnal mixing and rising motions to the oil tracers
298 subroutine oil_tracer_column_physics(h_old, h_new, ea, eb, fluxes, dt, G, GV, CS, tv, &
299  evap_CFL_limit, minimum_forcing_depth)
300  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
301  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
302  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
303  intent(in) :: h_old !< Layer thickness before entrainment [H ~> m or kg m-2].
304  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
305  intent(in) :: h_new !< Layer thickness after entrainment [H ~> m or kg m-2].
306  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
307  intent(in) :: ea !< an array to which the amount of fluid entrained
308  !! from the layer above during this call will be
309  !! added [H ~> m or kg m-2].
310  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
311  intent(in) :: eb !< an array to which the amount of fluid entrained
312  !! from the layer below during this call will be
313  !! added [H ~> m or kg m-2].
314  type(forcing), intent(in) :: fluxes !< A structure containing pointers to thermodynamic
315  !! and tracer forcing fields. Unused fields have NULL ptrs.
316  real, intent(in) :: dt !< The amount of time covered by this call [s]
317  type(oil_tracer_cs), pointer :: cs !< The control structure returned by a previous
318  !! call to register_oil_tracer.
319  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic variables
320  real, optional, intent(in) :: evap_cfl_limit !< Limit on the fraction of the water that can
321  !! be fluxed out of the top layer in a timestep [nondim]
322  real, optional, intent(in) :: minimum_forcing_depth !< The smallest depth over which
323  !! fluxes can be applied [m]
324 ! This subroutine applies diapycnal diffusion and any other column
325 ! tracer physics or chemistry to the tracers from this file.
326 ! This is a simple example of a set of advected passive tracers.
327 
328 ! The arguments to this subroutine are redundant in that
329 ! h_new(k) = h_old(k) + ea(k) - eb(k-1) + eb(k) - ea(k+1)
330 
331  ! Local variables
332  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: h_work ! Used so that h can be modified
333  real :: isecs_per_year = 1.0 / (365.0*86400.0)
334  real :: year, h_total, ldecay
335  integer :: i, j, k, is, ie, js, je, nz, m, k_max
336  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = gv%ke
337 
338  if (.not.associated(cs)) return
339  if (cs%ntr < 1) return
340 
341  if (present(evap_cfl_limit) .and. present(minimum_forcing_depth)) then
342  do m=1,cs%ntr
343  do k=1,nz ;do j=js,je ; do i=is,ie
344  h_work(i,j,k) = h_old(i,j,k)
345  enddo ; enddo ; enddo
346  call applytracerboundaryfluxesinout(g, gv, cs%tr(:,:,:,m) , dt, fluxes, h_work, &
347  evap_cfl_limit, minimum_forcing_depth)
348  call tracer_vertdiff(h_work, ea, eb, dt, cs%tr(:,:,:,m), g, gv)
349  enddo
350  else
351  do m=1,cs%ntr
352  call tracer_vertdiff(h_old, ea, eb, dt, cs%tr(:,:,:,m), g, gv)
353  enddo
354  endif
355 
356  year = time_type_to_real(cs%Time) * isecs_per_year
357 
358  ! Decay tracer (limit decay rate to 1/dt - just in case)
359  do m=2,cs%ntr
360  do k=1,nz ; do j=js,je ; do i=is,ie
361  !CS%tr(i,j,k,m) = CS%tr(i,j,k,m) - dt*CS%oil_decay_rate(m)*CS%tr(i,j,k,m) ! Simple
362  !CS%tr(i,j,k,m) = CS%tr(i,j,k,m) - min(dt*CS%oil_decay_rate(m),1.)*CS%tr(i,j,k,m) ! Safer
363  if (cs%oil_decay_rate(m)>0.) then
364  cs%tr(i,j,k,m) = g%mask2dT(i,j)*max(1.-dt*cs%oil_decay_rate(m),0.)*cs%tr(i,j,k,m) ! Safest
365  elseif (cs%oil_decay_rate(m)<0.) then
366  ldecay = 12.*(3.0**(-(tv%T(i,j,k)-20.)/10.)) ! Timescale [days]
367  ldecay = 1./(86400.*ldecay) ! Rate [s-1]
368  cs%tr(i,j,k,m) = g%mask2dT(i,j)*max(1.-dt*ldecay,0.)*cs%tr(i,j,k,m)
369  endif
370  enddo ; enddo ; enddo
371  enddo
372 
373  ! Add oil at the source location
374  if (year>=cs%oil_start_year .and. year<=cs%oil_end_year .and. &
375  cs%oil_source_i>-999 .and. cs%oil_source_j>-999) then
376  i=cs%oil_source_i ; j=cs%oil_source_j
377  k_max=nz ; h_total=0.
378  do k=nz, 2, -1
379  h_total = h_total + h_new(i,j,k)
380  if (h_total<10.) k_max=k-1 ! Find bottom most interface that is 10 m above bottom
381  enddo
382  do m=1,cs%ntr
383  k=cs%oil_source_k(m)
384  if (k>0) then
385  k=min(k,k_max) ! Only insert k or first layer with interface 10 m above bottom
386  cs%tr(i,j,k,m) = cs%tr(i,j,k,m) + cs%oil_source_rate*dt / &
387  ((h_new(i,j,k)+gv%H_subroundoff) * g%areaT(i,j) )
388  elseif (k<0) then
389  h_total=gv%H_subroundoff
390  do k=1, nz
391  h_total = h_total + h_new(i,j,k)
392  enddo
393  do k=1, nz
394  cs%tr(i,j,k,m) = cs%tr(i,j,k,m) + cs%oil_source_rate*dt/(h_total &
395  * g%areaT(i,j) )
396  enddo
397  endif
398  enddo
399  endif
400 
401 end subroutine oil_tracer_column_physics
402 
403 !> Calculate the mass-weighted integral of the oil tracer stocks, returning the number of stocks it
404 !! has calculated. If the stock_index is present, only the stock corresponding to that coded index is returned.
405 function oil_stock(h, stocks, G, GV, CS, names, units, stock_index)
406  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
407  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
408  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
409  real, dimension(:), intent(out) :: stocks !< the mass-weighted integrated amount of each
410  !! tracer, in kg times concentration units [kg conc].
411  type(oil_tracer_cs), pointer :: cs !< The control structure returned by a previous
412  !! call to register_oil_tracer.
413  character(len=*), dimension(:), intent(out) :: names !< the names of the stocks calculated.
414  character(len=*), dimension(:), intent(out) :: units !< the units of the stocks calculated.
415  integer, optional, intent(in) :: stock_index !< the coded index of a specific stock
416  !! being sought.
417  integer :: oil_stock !< The number of stocks calculated here.
418 
419 ! This function calculates the mass-weighted integral of all tracer stocks,
420 ! returning the number of stocks it has calculated. If the stock_index
421 ! is present, only the stock corresponding to that coded index is returned.
422 
423  ! Local variables
424  integer :: i, j, k, is, ie, js, je, nz, m
425  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = gv%ke
426 
427  oil_stock = 0
428  if (.not.associated(cs)) return
429  if (cs%ntr < 1) return
430 
431  if (present(stock_index)) then ; if (stock_index > 0) then
432  ! Check whether this stock is available from this routine.
433 
434  ! No stocks from this routine are being checked yet. Return 0.
435  return
436  endif ; endif
437 
438  do m=1,cs%ntr
439  call query_vardesc(cs%tr_desc(m), name=names(m), units=units(m), caller="oil_stock")
440  units(m) = trim(units(m))//" kg"
441  stocks(m) = 0.0
442  do k=1,nz ; do j=js,je ; do i=is,ie
443  stocks(m) = stocks(m) + cs%tr(i,j,k,m) * &
444  (g%mask2dT(i,j) * g%areaT(i,j) * h(i,j,k))
445  enddo ; enddo ; enddo
446  stocks(m) = gv%H_to_kg_m2 * stocks(m)
447  enddo
448  oil_stock = cs%ntr
449 
450 end function oil_stock
451 
452 !> This subroutine extracts the surface fields from this tracer package that
453 !! are to be shared with the atmosphere in coupled configurations.
454 !! This particular tracer package does not report anything back to the coupler.
455 subroutine oil_tracer_surface_state(state, h, G, CS)
456  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure.
457  type(surface), intent(inout) :: state !< A structure containing fields that
458  !! describe the surface state of the ocean.
459  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
460  intent(in) :: h !< Layer thickness [H ~> m or kg m-2].
461  type(oil_tracer_cs), pointer :: cs !< The control structure returned by a previous
462  !! call to register_oil_tracer.
463 
464  ! This particular tracer package does not report anything back to the coupler.
465  ! The code that is here is just a rough guide for packages that would.
466 
467  integer :: m, is, ie, js, je, isd, ied, jsd, jed
468  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
469  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
470 
471  if (.not.associated(cs)) return
472 
473  if (cs%coupled_tracers) then
474  do m=1,cs%ntr
475  ! This call loads the surface values into the appropriate array in the
476  ! coupler-type structure.
477  call coupler_type_set_data(cs%tr(:,:,1,m), cs%ind_tr(m), ind_csurf, &
478  state%tr_fields, idim=(/isd, is, ie, ied/), &
479  jdim=(/jsd, js, je, jed/) )
480  enddo
481  endif
482 
483 end subroutine oil_tracer_surface_state
484 
485 !> Deallocate memory associated with this tracer package
486 subroutine oil_tracer_end(CS)
487  type(oil_tracer_cs), pointer :: cs !< The control structure returned by a previous
488  !! call to register_oil_tracer.
489  integer :: m
490 
491  if (associated(cs)) then
492  if (associated(cs%tr)) deallocate(cs%tr)
493  deallocate(cs)
494  endif
495 end subroutine oil_tracer_end
496 
497 !> \namespace oil_tracer
498 !!
499 !! By Alistair Adcroft and Robert Hallberg, 2010 *
500 !!
501 !! In the midst of the Deepwater Horizon oil spill, it became evident that
502 !! models were needed to predict the long-term fate of dissolved oil in the
503 !! open ocean. This tracer packages mimics the transport, dilution and decay
504 !! of dissolved oil plumes in the ocean.
505 !!
506 !! This tracer package was central to the simulations used by Adcroft et al.,
507 !! GRL 2010, to prove that the Deepwater Horizon spill was an important regional
508 !! event, with implications for dissolved oxygen levels in the Gulf of Mexico,
509 !! but not one that would directly impact the East Coast of the U.S.
510 
511 end module oil_tracer
mom_time_manager
Wraps the FMS time manager functions.
Definition: MOM_time_manager.F90:2
mom_variables::surface
Pointers to various fields which may be used describe the surface state of MOM, and which will be ret...
Definition: MOM_variables.F90:38
mom_verticalgrid
Provides a transparent vertical ocean grid type and supporting routines.
Definition: MOM_verticalGrid.F90:2
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
atmos_ocean_fluxes_mod
A dummy version of atmos_ocean_fluxes_mod module for use when the vastly larger FMS package is not ne...
Definition: atmos_ocean_fluxes.F90:3
mom_diag_mediator
The subroutines here provide convenient wrappers to the fms diag_manager interfaces with additional d...
Definition: MOM_diag_mediator.F90:3
mom_variables::thermo_var_ptrs
Pointers to an assortment of thermodynamic fields that may be available, including potential temperat...
Definition: MOM_variables.F90:82
oil_tracer::oil_tracer_cs
The control structure for the oil tracer package.
Definition: oil_tracer.F90:38
mom_tracer_registry
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
Definition: MOM_tracer_registry.F90:5
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_hor_index
Defines the horizontal index type (hor_index_type) used for providing index ranges.
Definition: MOM_hor_index.F90:2
mom_io
This module contains I/O framework code.
Definition: MOM_io.F90:2
mom_restart::mom_restart_cs
A restart registry and the control structure for restarts.
Definition: MOM_restart.F90:72
mom_tracer_z_init
Used to initialize tracers from a depth- (or z*-) space file.
Definition: MOM_tracer_Z_init.F90:2
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_tracer_diabatic
This module contains routines that implement physical fluxes of tracers (e.g. due to surface fluxes o...
Definition: MOM_tracer_diabatic.F90:4
mom_forcing_type
This module implements boundary forcing for MOM6.
Definition: MOM_forcing_type.F90:2
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_restart
The MOM6 facility for reading and writing restart files, and querying what has been read.
Definition: MOM_restart.F90:2
mom_variables
Provides transparent structures with groups of MOM6 variables and supporting routines.
Definition: MOM_variables.F90:2
mom_io::mom_read_data
Read a data field from a file.
Definition: MOM_io.F90:74
mom_open_boundary
Controls where open boundary conditions are applied.
Definition: MOM_open_boundary.F90:2
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_sponge
Implements sponge regions in isopycnal mode.
Definition: MOM_sponge.F90:2
mom_tracer_registry::tracer_registry_type
Type to carry basic tracer information.
Definition: MOM_tracer_registry.F90:122
mom_hor_index::hor_index_type
Container for horizontal index ranges for data, computational and global domains.
Definition: MOM_hor_index.F90:15
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_open_boundary::ocean_obc_type
Open-boundary data.
Definition: MOM_open_boundary.F90:186
mom_sponge::sponge_cs
This control structure holds memory and parameters for the MOM_sponge module.
Definition: MOM_sponge.F90:40
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
mom_forcing_type::forcing
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
Definition: MOM_forcing_type.F90:49
mom_io::vardesc
Type for describing a variable, typically a tracer.
Definition: MOM_io.F90:53
mom_io::file_exists
Indicate whether a file exists, perhaps with domain decomposition.
Definition: MOM_io.F90:68
oil_tracer
A tracer package to mimic dissolved oil.
Definition: oil_tracer.F90:2
mom_file_parser::log_param
An overloaded interface to log the values of various types of parameters.
Definition: MOM_file_parser.F90:96
mom_restart::query_initialized
Indicate whether a field has been read from a restart file.
Definition: MOM_restart.F90:116
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25
mom_diag_mediator::diag_ctrl
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Definition: MOM_diag_mediator.F90:239