MOM6
mom_tracer_z_init Module Reference

Functions/Subroutines

logical function, public tracer_z_init (tr, h, filename, tr_name, G, missing_val, land_val)
 
subroutine read_z_edges (filename, tr_name, z_edges, nz_out, has_edges, use_missing, missing)
 

Function/Subroutine Documentation

◆ read_z_edges()

subroutine mom_tracer_z_init::read_z_edges ( character(len=*), intent(in)  filename,
character(len=*), intent(in)  tr_name,
real, dimension(:), intent(out), allocatable  z_edges,
integer, intent(out)  nz_out,
logical, intent(out)  has_edges,
logical, intent(inout)  use_missing,
real, intent(inout)  missing 
)
private

Definition at line 311 of file MOM_tracer_Z_init.F90.

References mom_error_handler::mom_error(), and mom_error_handler::mom_mesg().

Referenced by tracer_z_init().

311  character(len=*), intent(in) :: filename, tr_name
312  real, allocatable, dimension(:), intent(out) :: z_edges
313  integer, intent(out) :: nz_out
314  logical, intent(out) :: has_edges
315  logical, intent(inout) :: use_missing
316  real, intent(inout) :: missing
317 ! This subroutine reads the vertical coordinate data for a field from a
318 ! NetCDF file. It also might read the missing value attribute for that
319 ! same field.
320 ! Arguments: filename - The file to be read from.
321 ! (in) tr_name - The name of the tracer to be read.
322 ! (out) z_edges - The depths of the vertical edges of the tracer array.
323 ! (out) nz_out - The number of vertical layers in the tracer array.
324 ! (out) has_edges - If true, the values in z_edges are the edges of the
325 ! tracer cells, otherwise they are the cell centers.
326 ! (inout) use_missing - If false on input, see whether the tracer has a
327 ! missing value, and if so return true.
328 ! (inout) missing - The missing value, if one has been found.
329 
330  character(len=32) :: mdl
331  character(len=120) :: dim_name, edge_name, tr_msg, dim_msg
332  logical :: monotonic
333  integer :: ncid, status, intid, tr_id, layid, k
334  integer :: nz_edge, ndim, tr_dim_ids(nf90_max_var_dims)
335 
336  mdl = "MOM_tracer_Z_init read_Z_edges: "
337  tr_msg = trim(tr_name)//" in "//trim(filename)
338 
339  status = nf90_open(filename, nf90_nowrite, ncid);
340  if (status /= nf90_noerr) then
341  call mom_error(warning,mdl//" Difficulties opening "//trim(filename)//&
342  " - "//trim(nf90_strerror(status)))
343  nz_out = -1 ; return
344  endif
345 
346  status = nf90_inq_varid(ncid, tr_name, tr_id)
347  if (status /= nf90_noerr) then
348  call mom_error(warning,mdl//" Difficulties finding variable "//&
349  trim(tr_msg)//" - "//trim(nf90_strerror(status)))
350  nz_out = -1 ; status = nf90_close(ncid) ; return
351  endif
352  status = nf90_inquire_variable(ncid, tr_id, ndims=ndim, dimids=tr_dim_ids)
353  if (status /= nf90_noerr) then
354  call mom_error(warning,mdl//" cannot inquire about "//trim(tr_msg))
355  elseif ((ndim < 3) .or. (ndim > 4)) then
356  call mom_error(warning,mdl//" "//trim(tr_msg)//&
357  " has too many or too few dimensions.")
358  nz_out = -1 ; status = nf90_close(ncid) ; return
359  endif
360 
361  if (.not.use_missing) then
362  ! Try to find the missing value from the dataset.
363  status = nf90_get_att(ncid, tr_id, "missing_value", missing)
364  if (status /= nf90_noerr) use_missing = .true.
365  endif
366 
367  ! Get the axis name and length.
368  status = nf90_inquire_dimension(ncid, tr_dim_ids(3), dim_name, len=nz_out)
369  if (status /= nf90_noerr) then
370  call mom_error(warning,mdl//" cannot inquire about dimension(3) of "//&
371  trim(tr_msg))
372  endif
373 
374  dim_msg = trim(dim_name)//" in "//trim(filename)
375  status = nf90_inq_varid(ncid, dim_name, layid)
376  if (status /= nf90_noerr) then
377  call mom_error(warning,mdl//" Difficulties finding variable "//&
378  trim(dim_msg)//" - "//trim(nf90_strerror(status)))
379  nz_out = -1 ; status = nf90_close(ncid) ; return
380  endif
381  ! Find out if the Z-axis has an edges attribute
382  status = nf90_get_att(ncid, layid, "edges", edge_name)
383  if (status /= nf90_noerr) then
384  call mom_mesg(mdl//" "//trim(dim_msg)//&
385  " has no readable edges attribute - "//trim(nf90_strerror(status)))
386  has_edges = .false.
387  else
388  has_edges = .true.
389  status = nf90_inq_varid(ncid, edge_name, intid)
390  if (status /= nf90_noerr) then
391  call mom_error(warning,mdl//" Difficulties finding edge variable "//&
392  trim(edge_name)//" in "//trim(filename)//" - "//trim(nf90_strerror(status)))
393  has_edges = .false.
394  endif
395  endif
396 
397  nz_edge = nz_out ; if (has_edges) nz_edge = nz_out+1
398  allocate(z_edges(nz_edge)) ; z_edges(:) = 0.0
399 
400  if (nz_out < 1) return
401 
402  ! Read the right variable.
403  if (has_edges) then
404  dim_msg = trim(edge_name)//" in "//trim(filename)
405  status = nf90_get_var(ncid, intid, z_edges)
406  if (status /= nf90_noerr) then
407  call mom_error(warning,mdl//" Difficulties reading variable "//&
408  trim(dim_msg)//" - "//trim(nf90_strerror(status)))
409  nz_out = -1 ; status = nf90_close(ncid) ; return
410  endif
411  else
412  status = nf90_get_var(ncid, layid, z_edges)
413  if (status /= nf90_noerr) then
414  call mom_error(warning,mdl//" Difficulties reading variable "//&
415  trim(dim_msg)//" - "//trim(nf90_strerror(status)))
416  nz_out = -1 ; status = nf90_close(ncid) ; return
417  endif
418  endif
419 
420  status = nf90_close(ncid)
421  if (status /= nf90_noerr) call mom_error(warning, mdl// &
422  " Difficulties closing "//trim(filename)//" - "//trim(nf90_strerror(status)))
423 
424  ! z_edges should be montonically decreasing with our sign convention.
425  ! Change the sign sign convention if it looks like z_edges is increasing.
426  if (z_edges(1) < z_edges(2)) then
427  do k=1,nz_edge ; z_edges(k) = -z_edges(k) ; enddo
428  endif
429  ! Check that z_edges is now monotonically decreasing.
430  monotonic = .true.
431  do k=2,nz_edge ; if (z_edges(k) >= z_edges(k-1)) monotonic = .false. ; enddo
432  if (.not.monotonic) &
433  call mom_error(warning,mdl//" "//trim(dim_msg)//" is not monotonic.")
434 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ tracer_z_init()

logical function, public mom_tracer_z_init::tracer_z_init ( real, dimension(szi_(g),szj_(g),szk_(g)), intent(out)  tr,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  h,
character(len=*), intent(in)  filename,
character(len=*), intent(in)  tr_name,
type(ocean_grid_type), intent(in)  G,
real, intent(in), optional  missing_val,
real, intent(in), optional  land_val 
)
Parameters
[in]gThe ocean's grid structure
[in]hLayer thicknesses, in H (usually m or kg m-2)

Definition at line 60 of file MOM_tracer_Z_init.F90.

References mom_diag_to_z::find_limited_slope(), mom_diag_to_z::find_overlap(), mom_error_handler::mom_error(), and read_z_edges().

Referenced by mom_ocmip2_cfc::init_tracer_cfc(), ideal_age_example::initialize_ideal_age_tracer(), and oil_tracer::initialize_oil_tracer().

60  logical :: tracer_z_init
61  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
62  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(out) :: tr
63  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
64  character(len=*), intent(in) :: filename, tr_name
65 ! type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
66  real, optional, intent(in) :: missing_val
67  real, optional, intent(in) :: land_val
68 ! This function initializes a tracer by reading a Z-space file, returning
69 ! .true. if this appears to have been successful, and false otherwise.
70 ! Arguments: tr - The tracer to initialize.
71 ! (in) h - Layer thickness, in m or kg m-2.
72 ! (in) filename - The name of the file to read from.
73 ! (in) tr_name - The name of the tracer in the file.
74 ! (in) G - The ocean's grid structure.
75 ! (in) param_file - A structure indicating the open file to parse for
76 ! model parameter values.
77 ! (in,opt) missing_val - The missing value for the tracer.
78 ! (in,opt) land_val - The value to use to fill in land points.
79  integer, save :: init_calls = 0
80 ! This include declares and sets the variable "version".
81 #include "version_variable.h"
82  character(len=40) :: mdl = "MOM_tracer_Z_init" ! This module's name.
83  character(len=256) :: mesg ! Message for error messages.
84 
85  real, allocatable, dimension(:,:,:) :: &
86  tr_in ! The z-space array of tracer concentrations that is read in.
87  real, allocatable, dimension(:) :: &
88  z_edges, & ! The depths of the cell edges or cell centers (depending on
89  ! the value of has_edges) in the input z* data.
90  tr_1d, & ! A copy of the input tracer concentrations in a column.
91  wt, & ! The fractional weight for each layer in the range between
92  ! k_top and k_bot, nondim.
93  z1, & ! z1 and z2 are the depths of the top and bottom limits of the part
94  z2 ! of a z-cell that contributes to a layer, relative to the cell
95  ! center and normalized by the cell thickness, nondim.
96  ! Note that -1/2 <= z1 <= z2 <= 1/2.
97  real :: e(szk_(g)+1) ! The z-star interface heights in m.
98  real :: landval ! The tracer value to use in land points.
99  real :: sl_tr ! The normalized slope of the tracer
100  ! within the cell, in tracer units.
101  real :: htot(szi_(g)) ! The vertical sum of h, in m or kg m-2.
102  real :: dilate ! The amount by which the thicknesses are dilated to
103  ! create a z-star coordinate, nondim or in m3 kg-1.
104  real :: missing ! The missing value for the tracer.
105 
106  logical :: has_edges, use_missing, zero_surface
107  character(len=80) :: loc_msg
108  integer :: k_top, k_bot, k_bot_prev
109  integer :: i, j, k, kz, is, ie, js, je, nz, nz_in
110  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
111 
112  landval = 0.0 ; if (present(land_val)) landval = land_val
113 
114  zero_surface = .false. ! Make this false for errors to be fatal.
115 
116  use_missing = .false.
117  if (present(missing_val)) then
118  use_missing = .true. ; missing = missing_val
119  endif
120 
121  ! Find out the number of input levels and read the depth of the edges,
122  ! also modifying their sign convention to be monotonically decreasing.
123  call read_z_edges(filename, tr_name, z_edges, nz_in, has_edges, use_missing, missing)
124  if (nz_in < 1) then
125  tracer_z_init = .false.
126  return
127  endif
128 
129  allocate(tr_in(g%isd:g%ied,g%jsd:g%jed,nz_in)) ; tr_in(:,:,:) = 0.0
130  allocate(tr_1d(nz_in)) ; tr_1d(:) = 0.0
131  call read_data(filename, tr_name, tr_in(:,:,:), domain=g%Domain%mpp_domain)
132 
133  ! Fill missing values from above? Use a "close" test to avoid problems
134  ! from type-conversion rounoff.
135  if (present(missing_val)) then
136  do j=js,je ; do i=is,ie
137  if (g%mask2dT(i,j) == 0.0) then
138  tr_in(i,j,1) = landval
139  elseif (abs(tr_in(i,j,1) - missing_val) <= 1e-6*abs(missing_val)) then
140  write(loc_msg,'(f7.2," N ",f7.2," E")') g%geoLatT(i,j), g%geoLonT(i,j)
141  if (zero_surface) then
142  call mom_error(warning, "tracer_Z_init: Missing value of "// &
143  trim(tr_name)//" found in an ocean point at "//trim(loc_msg)// &
144  " in "//trim(filename) )
145  tr_in(i,j,1) = 0.0
146  else
147  call mom_error(fatal, "tracer_Z_init: Missing value of "// &
148  trim(tr_name)//" found in an ocean point at "//trim(loc_msg)// &
149  " in "//trim(filename) )
150  endif
151  endif
152  enddo ; enddo
153  do k=2,nz_in ; do j=js,je ; do i=is,ie
154  if (abs(tr_in(i,j,k) - missing_val) <= 1e-6*abs(missing_val)) &
155  tr_in(i,j,k) = tr_in(i,j,k-1)
156  enddo ; enddo ; enddo
157  endif
158 
159  allocate(wt(nz_in+1)) ; allocate(z1(nz_in+1)) ; allocate(z2(nz_in+1))
160 
161  ! This is a placeholder, and will be replaced with our full vertical
162  ! interpolation machinery when it is in place.
163  if (has_edges) then
164  do j=js,je
165  do i=is,ie ; htot(i) = 0.0 ; enddo
166  do k=1,nz ; do i=is,ie ; htot(i) = htot(i) + h(i,j,k) ; enddo ; enddo
167 
168  do i=is,ie ; if (g%mask2dT(i,j)*htot(i) > 0.0) then
169  ! Determine the z* heights of the model interfaces.
170  dilate = (g%bathyT(i,j) - 0.0) / htot(i)
171  e(nz+1) = -g%bathyT(i,j)
172  do k=nz,1,-1 ; e(k) = e(k+1) + dilate * h(i,j,k) ; enddo
173 
174  ! Create a single-column copy of tr_in. ### CHANGE THIS LATER?
175  do k=1,nz_in ; tr_1d(k) = tr_in(i,j,k) ; enddo
176  k_bot = 1 ; k_bot_prev = -1
177  do k=1,nz
178  if (e(k+1) > z_edges(1)) then
179  tr(i,j,k) = tr_1d(1)
180  elseif (e(k) < z_edges(nz_in+1)) then
181  tr(i,j,k) = tr_1d(nz_in)
182  else
183  call find_overlap(z_edges, e(k), e(k+1), nz_in, &
184  k_bot, k_top, k_bot, wt, z1, z2)
185  kz = k_top
186  if (kz /= k_bot_prev) then
187  ! Calculate the intra-cell profile.
188  sl_tr = 0.0 ! ; cur_tr = 0.0
189  if ((kz < nz_in) .and. (kz > 1)) call &
190  find_limited_slope(tr_1d, z_edges, sl_tr, kz)
191  endif
192  ! This is the piecewise linear form.
193  tr(i,j,k) = wt(kz) * &
194  (tr_1d(kz) + 0.5*sl_tr*(z2(kz) + z1(kz)))
195  ! For the piecewise parabolic form add the following...
196  ! + C1_3*cur_tr*(z2(kz)**2 + z2(kz)*z1(kz) + z1(kz)**2))
197  do kz=k_top+1,k_bot-1
198  tr(i,j,k) = tr(i,j,k) + wt(kz)*tr_1d(kz)
199  enddo
200  if (k_bot > k_top) then
201  kz = k_bot
202  ! Calculate the intra-cell profile.
203  sl_tr = 0.0 ! ; cur_tr = 0.0
204  if ((kz < nz_in) .and. (kz > 1)) call &
205  find_limited_slope(tr_1d, z_edges, sl_tr, kz)
206  ! This is the piecewise linear form.
207  tr(i,j,k) = tr(i,j,k) + wt(kz) * &
208  (tr_1d(kz) + 0.5*sl_tr*(z2(kz) + z1(kz)))
209  ! For the piecewise parabolic form add the following...
210  ! + C1_3*cur_tr*(z2(kz)**2 + z2(kz)*z1(kz) + z1(kz)**2))
211  endif
212  k_bot_prev = k_bot
213 
214  ! Now handle the unlikely case where the layer partially extends
215  ! past the valid range of the input data by extrapolating using
216  ! the top or bottom value.
217  if ((e(k) > z_edges(1)) .and. (z_edges(nz_in+1) > e(k+1))) then
218  tr(i,j,k) = (((e(k) - z_edges(1)) * tr_1d(1) + &
219  (z_edges(1) - z_edges(nz_in)) * tr(i,j,k)) + &
220  (z_edges(nz_in+1) - e(k+1)) * tr_1d(nz_in)) / &
221  (e(k) - e(k+1))
222  elseif (e(k) > z_edges(1)) then
223  tr(i,j,k) = ((e(k) - z_edges(1)) * tr_1d(1) + &
224  (z_edges(1) - e(k+1)) * tr(i,j,k)) / &
225  (e(k) - e(k+1))
226  elseif (z_edges(nz_in) > e(k+1)) then
227  tr(i,j,k) = ((e(k) - z_edges(nz_in+1)) * tr(i,j,k) + &
228  (z_edges(nz_in+1) - e(k+1)) * tr_1d(nz_in)) / &
229  (e(k) - e(k+1))
230  endif
231  endif
232  enddo ! k-loop
233  else
234  do k=1,nz ; tr(i,j,k) = landval ; enddo
235  endif ; enddo ! i-loop
236  enddo ! j-loop
237  else
238  ! Without edge values, integrate a linear interpolation between cell centers.
239  do j=js,je
240  do i=is,ie ; htot(i) = 0.0 ; enddo
241  do k=1,nz ; do i=is,ie ; htot(i) = htot(i) + h(i,j,k) ; enddo ; enddo
242 
243  do i=is,ie ; if (g%mask2dT(i,j)*htot(i) > 0.0) then
244  ! Determine the z* heights of the model interfaces.
245  dilate = (g%bathyT(i,j) - 0.0) / htot(i)
246  e(nz+1) = -g%bathyT(i,j)
247  do k=nz,1,-1 ; e(k) = e(k+1) + dilate * h(i,j,k) ; enddo
248 
249  ! Create a single-column copy of tr_in. ### CHANGE THIS LATER?
250  do k=1,nz_in ; tr_1d(k) = tr_in(i,j,k) ; enddo
251  k_bot = 1
252  do k=1,nz
253  if (e(k+1) > z_edges(1)) then
254  tr(i,j,k) = tr_1d(1)
255  elseif (z_edges(nz_in) > e(k)) then
256  tr(i,j,k) = tr_1d(nz_in)
257  else
258  call find_overlap(z_edges, e(k), e(k+1), nz_in-1, &
259  k_bot, k_top, k_bot, wt, z1, z2)
260 
261  kz = k_top
262  if (k_top < nz_in) then
263  tr(i,j,k) = wt(kz)*0.5*((tr_1d(kz) + tr_1d(kz+1)) + &
264  (tr_1d(kz+1) - tr_1d(kz))*(z2(kz)+z1(kz)))
265  else
266  tr(i,j,k) = wt(kz)*tr_1d(nz_in)
267  endif
268  do kz=k_top+1,k_bot-1
269  tr(i,j,k) = tr(i,j,k) + wt(kz)*0.5*(tr_1d(kz) + tr_1d(kz+1))
270  enddo
271  if (k_bot > k_top) then
272  kz = k_bot
273  tr(i,j,k) = tr(i,j,k) + wt(kz)*0.5*((tr_1d(kz) + tr_1d(kz+1)) + &
274  (tr_1d(kz+1) - tr_1d(kz))*(z2(kz)+z1(kz)))
275  endif
276 
277  ! Now handle the case where the layer partially extends past
278  ! the valid range of the input data.
279  if ((e(k) > z_edges(1)) .and. (z_edges(nz_in) > e(k+1))) then
280  tr(i,j,k) = (((e(k) - z_edges(1)) * tr_1d(1) + &
281  (z_edges(1) - z_edges(nz_in)) * tr(i,j,k)) + &
282  (z_edges(nz_in) - e(k+1)) * tr_1d(nz_in)) / &
283  (e(k) - e(k+1))
284  elseif (e(k) > z_edges(1)) then
285  tr(i,j,k) = ((e(k) - z_edges(1)) * tr_1d(1) + &
286  (z_edges(1) - e(k+1)) * tr(i,j,k)) / &
287  (e(k) - e(k+1))
288  elseif (z_edges(nz_in) > e(k+1)) then
289  tr(i,j,k) = ((e(k) - z_edges(nz_in)) * tr(i,j,k) + &
290  (z_edges(nz_in) - e(k+1)) * tr_1d(nz_in)) / &
291  (e(k) - e(k+1))
292  endif
293  endif
294  enddo
295  else
296  do k=1,nz ; tr(i,j,k) = landval ; enddo
297  endif ; enddo ! i-loop
298  enddo ! j-loop
299  endif
300 
301  deallocate(tr_in) ; deallocate(tr_1d) ; deallocate(z_edges)
302  deallocate(wt) ; deallocate(z1) ; deallocate(z2)
303 
304  tracer_z_init = .true.
305 
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Here is the call graph for this function:
Here is the caller graph for this function: