MOM6
MOM_grid.F90
Go to the documentation of this file.
1 !> Provides the ocean grid type
2 module mom_grid
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
7 use mom_domains, only : mom_domain_type, get_domain_extent, compute_block_extent
8 use mom_error_handler, only : mom_error, mom_mesg, fatal
10 
11 implicit none ; private
12 
13 #include <MOM_memory.h>
14 
17 
18 !> Ocean grid type. See mom_grid for details.
19 type, public :: ocean_grid_type
20  type(mom_domain_type), pointer :: domain => null() !< Ocean model domain
21  type(mom_domain_type), pointer :: domain_aux => null() !< A non-symmetric auxiliary domain type.
22  type(hor_index_type) :: hi !< Horizontal index ranges
23 
24  integer :: isc !< The start i-index of cell centers within the computational domain
25  integer :: iec !< The end i-index of cell centers within the computational domain
26  integer :: jsc !< The start j-index of cell centers within the computational domain
27  integer :: jec !< The end j-index of cell centers within the computational domain
28 
29  integer :: isd !< The start i-index of cell centers within the data domain
30  integer :: ied !< The end i-index of cell centers within the data domain
31  integer :: jsd !< The start j-index of cell centers within the data domain
32  integer :: jed !< The end j-index of cell centers within the data domain
33 
34  integer :: isg !< The start i-index of cell centers within the global domain
35  integer :: ieg !< The end i-index of cell centers within the global domain
36  integer :: jsg !< The start j-index of cell centers within the global domain
37  integer :: jeg !< The end j-index of cell centers within the global domain
38 
39  integer :: iscb !< The start i-index of cell vertices within the computational domain
40  integer :: iecb !< The end i-index of cell vertices within the computational domain
41  integer :: jscb !< The start j-index of cell vertices within the computational domain
42  integer :: jecb !< The end j-index of cell vertices within the computational domain
43 
44  integer :: isdb !< The start i-index of cell vertices within the data domain
45  integer :: iedb !< The end i-index of cell vertices within the data domain
46  integer :: jsdb !< The start j-index of cell vertices within the data domain
47  integer :: jedb !< The end j-index of cell vertices within the data domain
48 
49  integer :: isgb !< The start i-index of cell vertices within the global domain
50  integer :: iegb !< The end i-index of cell vertices within the global domain
51  integer :: jsgb !< The start j-index of cell vertices within the global domain
52  integer :: jegb !< The end j-index of cell vertices within the global domain
53 
54  integer :: isd_global !< The value of isd in the global index space (decompoistion invariant).
55  integer :: jsd_global !< The value of isd in the global index space (decompoistion invariant).
56  integer :: idg_offset !< The offset between the corresponding global and local i-indices.
57  integer :: jdg_offset !< The offset between the corresponding global and local j-indices.
58  integer :: ke !< The number of layers in the vertical.
59  logical :: symmetric !< True if symmetric memory is used.
60  logical :: nonblocking_updates !< If true, non-blocking halo updates are
61  !! allowed. The default is .false. (for now).
62  integer :: first_direction !< An integer that indicates which direction is
63  !! to be updated first in directionally split
64  !! parts of the calculation. This can be altered
65  !! during the course of the run via calls to
66  !! set_first_direction.
67 
68  real allocable_, dimension(NIMEM_,NJMEM_) :: &
69  mask2dt, & !< 0 for land points and 1 for ocean points on the h-grid. Nd.
70  geolatt, & !< The geographic latitude at q points in degrees of latitude or m.
71  geolont, & !< The geographic longitude at q points in degrees of longitude or m.
72  dxt, & !< dxT is delta x at h points, in m.
73  idxt, & !< 1/dxT in m-1.
74  dyt, & !< dyT is delta y at h points, in m, and IdyT is 1/dyT in m-1.
75  idyt, & !< dyT is delta y at h points, in m, and IdyT is 1/dyT in m-1.
76  areat, & !< The area of an h-cell, in m2.
77  iareat, & !< 1/areaT, in m-2.
78  sin_rot, & !< The sine of the angular rotation between the local model grid's northward
79  !! and the true northward directions.
80  cos_rot !< The cosine of the angular rotation between the local model grid's northward
81  !! and the true northward directions.
82 
83  real allocable_, dimension(NIMEMB_PTR_,NJMEM_) :: &
84  mask2dcu, & !< 0 for boundary points and 1 for ocean points on the u grid. Nondim.
85  geolatcu, & !< The geographic latitude at u points in degrees of latitude or m.
86  geoloncu, & !< The geographic longitude at u points in degrees of longitude or m.
87  dxcu, & !< dxCu is delta x at u points, in m.
88  idxcu, & !< 1/dxCu in m-1.
89  dycu, & !< dyCu is delta y at u points, in m.
90  idycu, & !< 1/dyCu in m-1.
91  dy_cu, & !< The unblocked lengths of the u-faces of the h-cell in m.
92  dy_cu_obc, & !< The unblocked lengths of the u-faces of the h-cell in m for OBC.
93  iareacu, & !< The masked inverse areas of u-grid cells in m2.
94  areacu !< The areas of the u-grid cells in m2.
95  !> \todo dy_Cu_obc is not used?
96 
97  real allocable_, dimension(NIMEM_,NJMEMB_PTR_) :: &
98  mask2dcv, & !< 0 for boundary points and 1 for ocean points on the v grid. Nondim.
99  geolatcv, & !< The geographic latitude at v points in degrees of latitude or m.
100  geoloncv, & !< The geographic longitude at v points in degrees of longitude or m.
101  dxcv, & !< dxCv is delta x at v points, in m.
102  idxcv, & !< 1/dxCv in m-1.
103  dycv, & !< dyCv is delta y at v points, in m.
104  idycv, & !< 1/dyCv in m-1.
105  dx_cv, & !< The unblocked lengths of the v-faces of the h-cell in m.
106  dx_cv_obc, & !< The unblocked lengths of the v-faces of the h-cell in m for OBC.
107  iareacv, & !< The masked inverse areas of v-grid cells in m2.
108  areacv !< The areas of the v-grid cells in m2.
109 
110  real allocable_, dimension(NIMEMB_PTR_,NJMEMB_PTR_) :: &
111  mask2dbu, & !< 0 for boundary points and 1 for ocean points on the q grid. Nondim.
112  geolatbu, & !< The geographic latitude at q points in degrees of latitude or m.
113  geolonbu, & !< The geographic longitude at q points in degrees of longitude or m.
114  dxbu, & !< dxBu is delta x at q points, in m.
115  idxbu, & !< 1/dxBu in m-1.
116  dybu, & !< dyBu is delta y at q points, in m.
117  idybu, & !< 1/dyBu in m-1.
118  areabu, & !< areaBu is the area of a q-cell, in m2
119  iareabu !< IareaBu = 1/areaBu in m-2.
120 
121  real, pointer, dimension(:) :: &
122  gridlatt => null(), & !< The latitude of T points for the purpose of labeling the output axes.
123  !! On many grids this is the same as geoLatT.
124  gridlatb => null() !< The latitude of B points for the purpose of labeling the output axes.
125  !! On many grids this is the same as geoLatBu.
126  real, pointer, dimension(:) :: &
127  gridlont => null(), & !< The longitude of T points for the purpose of labeling the output axes.
128  !! On many grids this is the same as geoLonT.
129  gridlonb => null() !< The longitude of B points for the purpose of labeling the output axes.
130  !! On many grids this is the same as geoLonBu.
131  character(len=40) :: &
132  x_axis_units, & !< The units that are used in labeling the x coordinate axes.
133  y_axis_units !< The units that are used in labeling the y coordinate axes.
134 
135  real allocable_, dimension(NIMEM_,NJMEM_) :: &
136  bathyt !< Ocean bottom depth at tracer points, in m.
137 
138  logical :: bathymetry_at_vel !< If true, there are separate values for the
139  !! basin depths at velocity points. Otherwise the effects of
140  !! of topography are entirely determined from thickness points.
141  real allocable_, dimension(NIMEMB_PTR_,NJMEM_) :: &
142  dblock_u, & !< Topographic depths at u-points at which the flow is blocked, in m.
143  dopen_u !< Topographic depths at u-points at which the flow is open at width dy_Cu, in m.
144  real allocable_, dimension(NIMEM_,NJMEMB_PTR_) :: &
145  dblock_v, & !< Topographic depths at v-points at which the flow is blocked, in m.
146  dopen_v !< Topographic depths at v-points at which the flow is open at width dx_Cv, in m.
147  real allocable_, dimension(NIMEMB_PTR_,NJMEMB_PTR_) :: &
148  coriolisbu !< The Coriolis parameter at corner points, in s-1.
149  real allocable_, dimension(NIMEM_,NJMEM_) :: &
150  df_dx, & !< Derivative d/dx f (Coriolis parameter) at h-points, in s-1 m-1.
151  df_dy !< Derivative d/dy f (Coriolis parameter) at h-points, in s-1 m-1.
152  real :: g_earth !< The gravitational acceleration in m s-2.
153 
154  ! These variables are global sums that are useful for 1-d diagnostics
155  real :: areat_global !< Global sum of h-cell area in m2
156  real :: iareat_global !< Global sum of inverse h-cell area (1/areaT_global) in m2.
157 
158  ! These variables are for block structures.
159  integer :: nblocks
160  type(hor_index_type), pointer :: block(:) => null() ! store indices for each block
161 
162  ! These parameters are run-time parameters that are used during some
163  ! initialization routines (but not all)
164  real :: south_lat !< The latitude (or y-coordinate) of the first v-line
165  real :: west_lon !< The longitude (or x-coordinate) of the first u-line
166  real :: len_lat = 0. !< The latitudinal (or y-coord) extent of physical domain
167  real :: len_lon = 0. !< The longitudinal (or x-coord) extent of physical domain
168  real :: rad_earth = 6.378e6 !< The radius of the planet in meters.
169  real :: max_depth !< The maximum depth of the ocean in meters.
170 end type ocean_grid_type
171 
172 contains
173 
174 !> MOM_grid_init initializes the ocean grid array sizes and grid memory.
175 subroutine mom_grid_init(G, param_file, HI, global_indexing, bathymetry_at_vel)
176  type(ocean_grid_type), intent(inout) :: G !< The horizontal grid type
177  type(param_file_type), intent(in) :: param_file !< Parameter file handle
178  type(hor_index_type), &
179  optional, intent(in) :: HI !< A hor_index_type for array extents
180  logical, optional, intent(in) :: global_indexing !< If true use global index
181  !! values instead of having the data domain on each
182  !! processor start at 1.
183  logical, optional, intent(in) :: bathymetry_at_vel !< If true, there are
184  !! separate values for the ocean bottom depths at
185  !! velocity points. Otherwise the effects of topography
186  !! are entirely determined from thickness points.
187 
188 ! This include declares and sets the variable "version".
189 #include "version_variable.h"
190  integer :: isd, ied, jsd, jed, nk
191  integer :: IsdB, IedB, JsdB, JedB
192  integer :: ied_max, jed_max
193  integer :: niblock, njblock, nihalo, njhalo, nblocks, n, i, j
194  logical :: local_indexing ! If false use global index values instead of having
195  ! the data domain on each processor start at 1.
196 
197  integer, allocatable, dimension(:) :: ibegin, iend, jbegin, jend
198  character(len=40) :: mod_nm = "MOM_grid" ! This module's name.
199 
200 
201  ! Read all relevant parameters and write them to the model log.
202  call log_version(param_file, mod_nm, version, &
203  "Parameters providing information about the lateral grid.")
204 
205 
206  call get_param(param_file, mod_nm, "NIBLOCK", niblock, "The number of blocks "// &
207  "in the x-direction on each processor (for openmp).", default=1, &
208  layoutparam=.true.)
209  call get_param(param_file, mod_nm, "NJBLOCK", njblock, "The number of blocks "// &
210  "in the y-direction on each processor (for openmp).", default=1, &
211  layoutparam=.true.)
212 
213  if (present(hi)) then
214  g%HI = hi
215 
216  g%isc = hi%isc ; g%iec = hi%iec ; g%jsc = hi%jsc ; g%jec = hi%jec
217  g%isd = hi%isd ; g%ied = hi%ied ; g%jsd = hi%jsd ; g%jed = hi%jed
218  g%isg = hi%isg ; g%ieg = hi%ieg ; g%jsg = hi%jsg ; g%jeg = hi%jeg
219 
220  g%IscB = hi%IscB ; g%IecB = hi%IecB ; g%JscB = hi%JscB ; g%JecB = hi%JecB
221  g%IsdB = hi%IsdB ; g%IedB = hi%IedB ; g%JsdB = hi%JsdB ; g%JedB = hi%JedB
222  g%IsgB = hi%IsgB ; g%IegB = hi%IegB ; g%JsgB = hi%JsgB ; g%JegB = hi%JegB
223 
224  g%idg_offset = hi%idg_offset ; g%jdg_offset = hi%jdg_offset
225  g%isd_global = g%isd + hi%idg_offset ; g%jsd_global = g%jsd + hi%jdg_offset
226  g%symmetric = hi%symmetric
227  else
228  local_indexing = .true.
229  if (present(global_indexing)) local_indexing = .not.global_indexing
230  call hor_index_init(g%Domain, g%HI, param_file, &
231  local_indexing=local_indexing)
232 
233  ! get_domain_extent ensures that domains start at 1 for compatibility between
234  ! static and dynamically allocated arrays, unless global_indexing is true.
235  call get_domain_extent(g%Domain, g%isc, g%iec, g%jsc, g%jec, &
236  g%isd, g%ied, g%jsd, g%jed, &
237  g%isg, g%ieg, g%jsg, g%jeg, &
238  g%idg_offset, g%jdg_offset, g%symmetric, &
239  local_indexing=local_indexing)
240  g%isd_global = g%isd+g%idg_offset ; g%jsd_global = g%jsd+g%jdg_offset
241  endif
242 
243  g%nonblocking_updates = g%Domain%nonblocking_updates
244 
245  ! Set array sizes for fields that are discretized at tracer cell boundaries.
246  g%IscB = g%isc ; g%JscB = g%jsc
247  g%IsdB = g%isd ; g%JsdB = g%jsd
248  g%IsgB = g%isg ; g%JsgB = g%jsg
249  if (g%symmetric) then
250  g%IscB = g%isc-1 ; g%JscB = g%jsc-1
251  g%IsdB = g%isd-1 ; g%JsdB = g%jsd-1
252  g%IsgB = g%isg-1 ; g%JsgB = g%jsg-1
253  endif
254  g%IecB = g%iec ; g%JecB = g%jec
255  g%IedB = g%ied ; g%JedB = g%jed
256  g%IegB = g%ieg ; g%JegB = g%jeg
257 
258  call mom_mesg(" MOM_grid.F90, MOM_grid_init: allocating metrics", 5)
259 
260  call allocate_metrics(g)
261 
262  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
263  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
264 
265  g%bathymetry_at_vel = .false.
266  if (present(bathymetry_at_vel)) g%bathymetry_at_vel = bathymetry_at_vel
267  if (g%bathymetry_at_vel) then
268  alloc_(g%Dblock_u(isdb:iedb, jsd:jed)) ; g%Dblock_u(:,:) = 0.0
269  alloc_(g%Dopen_u(isdb:iedb, jsd:jed)) ; g%Dopen_u(:,:) = 0.0
270  alloc_(g%Dblock_v(isd:ied, jsdb:jedb)) ; g%Dblock_v(:,:) = 0.0
271  alloc_(g%Dopen_v(isd:ied, jsdb:jedb)) ; g%Dopen_v(:,:) = 0.0
272  endif
273 
274 ! setup block indices.
275  nihalo = g%Domain%nihalo
276  njhalo = g%Domain%njhalo
277  nblocks = niblock * njblock
278  if (nblocks < 1) call mom_error(fatal, "MOM_grid_init: " // &
279  "nblocks(=NI_BLOCK*NJ_BLOCK) must be no less than 1")
280 
281  allocate(ibegin(niblock), iend(niblock), jbegin(njblock), jend(njblock))
282  call compute_block_extent(g%HI%isc,g%HI%iec,niblock,ibegin,iend)
283  call compute_block_extent(g%HI%jsc,g%HI%jec,njblock,jbegin,jend)
284  !-- make sure the last block is the largest.
285  do i = 1, niblock-1
286  if (iend(i)-ibegin(i) > iend(niblock)-ibegin(niblock) ) call mom_error(fatal, &
287  "MOM_grid_init: the last block size in x-direction is not the largest")
288  enddo
289  do j = 1, njblock-1
290  if (jend(j)-jbegin(j) > jend(njblock)-jbegin(njblock) ) call mom_error(fatal, &
291  "MOM_grid_init: the last block size in y-direction is not the largest")
292  enddo
293 
294  g%nblocks = nblocks
295  allocate(g%Block(nblocks))
296  ied_max = 1 ; jed_max = 1
297  do n = 1,nblocks
298  ! Copy all information from the array index type describing the local grid.
299  g%Block(n) = g%HI
300 
301  i = mod((n-1), niblock) + 1
302  j = (n-1)/niblock + 1
303  !--- isd and jsd are always 1 for each block to permit array reuse.
304  g%Block(n)%isd = 1 ; g%Block(n)%jsd = 1
305  g%Block(n)%isc = g%Block(n)%isd+nihalo
306  g%Block(n)%jsc = g%Block(n)%jsd+njhalo
307  g%Block(n)%iec = g%Block(n)%isc + iend(i) - ibegin(i)
308  g%Block(n)%jec = g%Block(n)%jsc + jend(j) - jbegin(j)
309  g%Block(n)%ied = g%Block(n)%iec + nihalo
310  g%Block(n)%jed = g%Block(n)%jec + njhalo
311  g%Block(n)%IscB = g%Block(n)%isc; g%Block(n)%IecB = g%Block(n)%iec
312  g%Block(n)%JscB = g%Block(n)%jsc; g%Block(n)%JecB = g%Block(n)%jec
313  ! For symmetric memory domains, the first block will have the extra point
314  ! at the lower boundary of its computational domain.
315  if (g%symmetric) then
316  if (i==1) g%Block(n)%IscB = g%Block(n)%IscB-1
317  if (j==1) g%Block(n)%JscB = g%Block(n)%JscB-1
318  endif
319  g%Block(n)%IsdB = g%Block(n)%isd; g%Block(n)%IedB = g%Block(n)%ied
320  g%Block(n)%JsdB = g%Block(n)%jsd; g%Block(n)%JedB = g%Block(n)%jed
321  !--- For symmetric memory domain, every block will have an extra point
322  !--- at the lower boundary of its data domain.
323  if (g%symmetric) then
324  g%Block(n)%IsdB = g%Block(n)%IsdB-1
325  g%Block(n)%JsdB = g%Block(n)%JsdB-1
326  endif
327  g%Block(n)%idg_offset = (ibegin(i) - g%Block(n)%isc) + g%HI%idg_offset
328  g%Block(n)%jdg_offset = (jbegin(j) - g%Block(n)%jsc) + g%HI%jdg_offset
329  ! Find the largest values of ied and jed so that all blocks will have the
330  ! same size in memory.
331  ied_max = max(ied_max, g%Block(n)%ied)
332  jed_max = max(jed_max, g%Block(n)%jed)
333  enddo
334 
335  ! Reset all of the data domain sizes to match the largest for array reuse,
336  ! recalling that all block have isd=jed=1 for array reuse.
337  do n = 1,nblocks
338  g%Block(n)%ied = ied_max ; g%Block(n)%IedB = ied_max
339  g%Block(n)%jed = jed_max ; g%Block(n)%JedB = jed_max
340  enddo
341 
342  !-- do some bounds error checking
343  if ( g%block(nblocks)%ied+g%block(nblocks)%idg_offset > g%HI%ied + g%HI%idg_offset ) &
344  call mom_error(fatal, "MOM_grid_init: G%ied_bk > G%ied")
345  if ( g%block(nblocks)%jed+g%block(nblocks)%jdg_offset > g%HI%jed + g%HI%jdg_offset ) &
346  call mom_error(fatal, "MOM_grid_init: G%jed_bk > G%jed")
347 
348 end subroutine mom_grid_init
349 
350 
351 !> set_derived_metrics calculates metric terms that are derived from other metrics.
352 subroutine set_derived_metrics(G)
353  type(ocean_grid_type), intent(inout) :: G !< The horizontal grid structure
354 ! Various inverse grid spacings and derived areas are calculated within this
355 ! subroutine.
356  integer :: i, j, isd, ied, jsd, jed
357  integer :: IsdB, IedB, JsdB, JedB
358 
359  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
360  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
361 
362  do j=jsd,jed ; do i=isd,ied
363  if (g%dxT(i,j) < 0.0) g%dxT(i,j) = 0.0
364  if (g%dyT(i,j) < 0.0) g%dyT(i,j) = 0.0
365  g%IdxT(i,j) = adcroft_reciprocal(g%dxT(i,j))
366  g%IdyT(i,j) = adcroft_reciprocal(g%dyT(i,j))
367  g%IareaT(i,j) = adcroft_reciprocal(g%areaT(i,j))
368  enddo ; enddo
369 
370  do j=jsd,jed ; do i=isdb,iedb
371  if (g%dxCu(i,j) < 0.0) g%dxCu(i,j) = 0.0
372  if (g%dyCu(i,j) < 0.0) g%dyCu(i,j) = 0.0
373  g%IdxCu(i,j) = adcroft_reciprocal(g%dxCu(i,j))
374  g%IdyCu(i,j) = adcroft_reciprocal(g%dyCu(i,j))
375  enddo ; enddo
376 
377  do j=jsdb,jedb ; do i=isd,ied
378  if (g%dxCv(i,j) < 0.0) g%dxCv(i,j) = 0.0
379  if (g%dyCv(i,j) < 0.0) g%dyCv(i,j) = 0.0
380  g%IdxCv(i,j) = adcroft_reciprocal(g%dxCv(i,j))
381  g%IdyCv(i,j) = adcroft_reciprocal(g%dyCv(i,j))
382  enddo ; enddo
383 
384  do j=jsdb,jedb ; do i=isdb,iedb
385  if (g%dxBu(i,j) < 0.0) g%dxBu(i,j) = 0.0
386  if (g%dyBu(i,j) < 0.0) g%dyBu(i,j) = 0.0
387 
388  g%IdxBu(i,j) = adcroft_reciprocal(g%dxBu(i,j))
389  g%IdyBu(i,j) = adcroft_reciprocal(g%dyBu(i,j))
390  ! areaBu has usually been set to a positive area elsewhere.
391  if (g%areaBu(i,j) <= 0.0) g%areaBu(i,j) = g%dxBu(i,j) * g%dyBu(i,j)
392  g%IareaBu(i,j) = adcroft_reciprocal(g%areaBu(i,j))
393  enddo ; enddo
394 end subroutine set_derived_metrics
395 
396 !> Adcroft_reciprocal(x) = 1/x for |x|>0 or 0 for x=0.
397 function adcroft_reciprocal(val) result(I_val)
398  real, intent(in) :: val !< The value being inverted.
399  real :: I_val !< The Adcroft reciprocal of val.
400 
401  i_val = 0.0 ; if (val /= 0.0) i_val = 1.0/val
402 end function adcroft_reciprocal
403 
404 !> Returns true if the coordinates (x,y) are within the h-cell (i,j)
405 logical function ispointincell(G, i, j, x, y)
406  type(ocean_grid_type), intent(in) :: G !< Grid type
407  integer, intent(in) :: i !< i index of cell to test
408  integer, intent(in) :: j !< j index of cell to test
409  real, intent(in) :: x !< x coordinate of point
410  real, intent(in) :: y !< y coordinate of point
411  ! Local variables
412  real :: xNE, xNW, xSE, xSW, yNE, yNW, ySE, ySW
413  real :: p0, p1, p2, p3, l0, l1, l2, l3
414  ispointincell = .false.
415  xne = g%geoLonBu(i ,j ) ; yne = g%geoLatBu(i ,j )
416  xnw = g%geoLonBu(i-1,j ) ; ynw = g%geoLatBu(i-1,j )
417  xse = g%geoLonBu(i ,j-1) ; yse = g%geoLatBu(i ,j-1)
418  xsw = g%geoLonBu(i-1,j-1) ; ysw = g%geoLatBu(i-1,j-1)
419  ! This is a crude calculation that assume a geographic coordinate system
420  if (x<min(xne,xnw,xse,xsw) .or. x>max(xne,xnw,xse,xsw) .or. &
421  y<min(yne,ynw,yse,ysw) .or. y>max(yne,ynw,yse,ysw) ) then
422  return ! Avoid the more complicated calculation
423  endif
424  l0 = (x-xsw)*(yse-ysw) - (y-ysw)*(xse-xsw)
425  l1 = (x-xse)*(yne-yse) - (y-yse)*(xne-xse)
426  l2 = (x-xne)*(ynw-yne) - (y-yne)*(xnw-xne)
427  l3 = (x-xnw)*(ysw-ynw) - (y-ynw)*(xsw-xnw)
428 
429  p0 = sign(1., l0) ; if (l0 == 0.) p0=0.
430  p1 = sign(1., l1) ; if (l1 == 0.) p1=0.
431  p2 = sign(1., l2) ; if (l2 == 0.) p2=0.
432  p3 = sign(1., l3) ; if (l3 == 0.) p3=0.
433 
434  if ( (abs(p0)+abs(p2)) + (abs(p1)+abs(p3)) == abs((p0+p2) + (p1+p3)) ) then
435  ispointincell=.true.
436  endif
437 end function ispointincell
438 
439 subroutine set_first_direction(G, y_first)
440  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
441  integer, intent(in) :: y_first
442 
443  g%first_direction = y_first
444 end subroutine set_first_direction
445 
446 !> Allocate memory used by the ocean_grid_type and related structures.
447 subroutine allocate_metrics(G)
448  type(ocean_grid_type), intent(inout) :: G !< The horizontal grid type
449  integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB, isg, ieg, jsg, jeg
450 
451  ! This subroutine allocates the lateral elements of the ocean_grid_type that
452  ! are always used and zeros them out.
453 
454  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
455  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
456  isg = g%isg ; ieg = g%ieg ; jsg = g%jsg ; jeg = g%jeg
457 
458  alloc_(g%dxT(isd:ied,jsd:jed)) ; g%dxT(:,:) = 0.0
459  alloc_(g%dxCu(isdb:iedb,jsd:jed)) ; g%dxCu(:,:) = 0.0
460  alloc_(g%dxCv(isd:ied,jsdb:jedb)) ; g%dxCv(:,:) = 0.0
461  alloc_(g%dxBu(isdb:iedb,jsdb:jedb)) ; g%dxBu(:,:) = 0.0
462  alloc_(g%IdxT(isd:ied,jsd:jed)) ; g%IdxT(:,:) = 0.0
463  alloc_(g%IdxCu(isdb:iedb,jsd:jed)) ; g%IdxCu(:,:) = 0.0
464  alloc_(g%IdxCv(isd:ied,jsdb:jedb)) ; g%IdxCv(:,:) = 0.0
465  alloc_(g%IdxBu(isdb:iedb,jsdb:jedb)) ; g%IdxBu(:,:) = 0.0
466 
467  alloc_(g%dyT(isd:ied,jsd:jed)) ; g%dyT(:,:) = 0.0
468  alloc_(g%dyCu(isdb:iedb,jsd:jed)) ; g%dyCu(:,:) = 0.0
469  alloc_(g%dyCv(isd:ied,jsdb:jedb)) ; g%dyCv(:,:) = 0.0
470  alloc_(g%dyBu(isdb:iedb,jsdb:jedb)) ; g%dyBu(:,:) = 0.0
471  alloc_(g%IdyT(isd:ied,jsd:jed)) ; g%IdyT(:,:) = 0.0
472  alloc_(g%IdyCu(isdb:iedb,jsd:jed)) ; g%IdyCu(:,:) = 0.0
473  alloc_(g%IdyCv(isd:ied,jsdb:jedb)) ; g%IdyCv(:,:) = 0.0
474  alloc_(g%IdyBu(isdb:iedb,jsdb:jedb)) ; g%IdyBu(:,:) = 0.0
475 
476  alloc_(g%areaT(isd:ied,jsd:jed)) ; g%areaT(:,:) = 0.0
477  alloc_(g%IareaT(isd:ied,jsd:jed)) ; g%IareaT(:,:) = 0.0
478  alloc_(g%areaBu(isdb:iedb,jsdb:jedb)) ; g%areaBu(:,:) = 0.0
479  alloc_(g%IareaBu(isdb:iedb,jsdb:jedb)) ; g%IareaBu(:,:) = 0.0
480 
481  alloc_(g%mask2dT(isd:ied,jsd:jed)) ; g%mask2dT(:,:) = 0.0
482  alloc_(g%mask2dCu(isdb:iedb,jsd:jed)) ; g%mask2dCu(:,:) = 0.0
483  alloc_(g%mask2dCv(isd:ied,jsdb:jedb)) ; g%mask2dCv(:,:) = 0.0
484  alloc_(g%mask2dBu(isdb:iedb,jsdb:jedb)) ; g%mask2dBu(:,:) = 0.0
485  alloc_(g%geoLatT(isd:ied,jsd:jed)) ; g%geoLatT(:,:) = 0.0
486  alloc_(g%geoLatCu(isdb:iedb,jsd:jed)) ; g%geoLatCu(:,:) = 0.0
487  alloc_(g%geoLatCv(isd:ied,jsdb:jedb)) ; g%geoLatCv(:,:) = 0.0
488  alloc_(g%geoLatBu(isdb:iedb,jsdb:jedb)) ; g%geoLatBu(:,:) = 0.0
489  alloc_(g%geoLonT(isd:ied,jsd:jed)) ; g%geoLonT(:,:) = 0.0
490  alloc_(g%geoLonCu(isdb:iedb,jsd:jed)) ; g%geoLonCu(:,:) = 0.0
491  alloc_(g%geoLonCv(isd:ied,jsdb:jedb)) ; g%geoLonCv(:,:) = 0.0
492  alloc_(g%geoLonBu(isdb:iedb,jsdb:jedb)) ; g%geoLonBu(:,:) = 0.0
493 
494  alloc_(g%dx_Cv(isd:ied,jsdb:jedb)) ; g%dx_Cv(:,:) = 0.0
495  alloc_(g%dy_Cu(isdb:iedb,jsd:jed)) ; g%dy_Cu(:,:) = 0.0
496  alloc_(g%dx_Cv_obc(isd:ied,jsdb:jedb)) ; g%dx_Cv_obc(:,:) = 0.0
497  alloc_(g%dy_Cu_obc(isdb:iedb,jsd:jed)) ; g%dy_Cu_obc(:,:) = 0.0
498 
499  alloc_(g%areaCu(isdb:iedb,jsd:jed)) ; g%areaCu(:,:) = 0.0
500  alloc_(g%areaCv(isd:ied,jsdb:jedb)) ; g%areaCv(:,:) = 0.0
501  alloc_(g%IareaCu(isdb:iedb,jsd:jed)) ; g%IareaCu(:,:) = 0.0
502  alloc_(g%IareaCv(isd:ied,jsdb:jedb)) ; g%IareaCv(:,:) = 0.0
503 
504  alloc_(g%bathyT(isd:ied, jsd:jed)) ; g%bathyT(:,:) = 0.0
505  alloc_(g%CoriolisBu(isdb:iedb, jsdb:jedb)) ; g%CoriolisBu(:,:) = 0.0
506  alloc_(g%dF_dx(isd:ied, jsd:jed)) ; g%dF_dx(:,:) = 0.0
507  alloc_(g%dF_dy(isd:ied, jsd:jed)) ; g%dF_dy(:,:) = 0.0
508 
509  alloc_(g%sin_rot(isd:ied,jsd:jed)) ; g%sin_rot(:,:) = 0.0
510  alloc_(g%cos_rot(isd:ied,jsd:jed)) ; g%cos_rot(:,:) = 1.0
511 
512  allocate(g%gridLonT(isg:ieg)) ; g%gridLonT(:) = 0.0
513  allocate(g%gridLonB(g%IsgB:g%IegB)) ; g%gridLonB(:) = 0.0
514  allocate(g%gridLatT(jsg:jeg)) ; g%gridLatT(:) = 0.0
515  allocate(g%gridLatB(g%JsgB:g%JegB)) ; g%gridLatB(:) = 0.0
516 
517 end subroutine allocate_metrics
518 
519 !> Release memory used by the ocean_grid_type and related structures.
520 subroutine mom_grid_end(G)
521  type(ocean_grid_type), intent(inout) :: G !< The horizontal grid type
522 
523  dealloc_(g%dxT) ; dealloc_(g%dxCu) ; dealloc_(g%dxCv) ; dealloc_(g%dxBu)
524  dealloc_(g%IdxT) ; dealloc_(g%IdxCu) ; dealloc_(g%IdxCv) ; dealloc_(g%IdxBu)
525 
526  dealloc_(g%dyT) ; dealloc_(g%dyCu) ; dealloc_(g%dyCv) ; dealloc_(g%dyBu)
527  dealloc_(g%IdyT) ; dealloc_(g%IdyCu) ; dealloc_(g%IdyCv) ; dealloc_(g%IdyBu)
528 
529  dealloc_(g%areaT) ; dealloc_(g%IareaT)
530  dealloc_(g%areaBu) ; dealloc_(g%IareaBu)
531  dealloc_(g%areaCu) ; dealloc_(g%IareaCu)
532  dealloc_(g%areaCv) ; dealloc_(g%IareaCv)
533 
534  dealloc_(g%mask2dT) ; dealloc_(g%mask2dCu)
535  dealloc_(g%mask2dCv) ; dealloc_(g%mask2dBu)
536 
537  dealloc_(g%geoLatT) ; dealloc_(g%geoLatCu)
538  dealloc_(g%geoLatCv) ; dealloc_(g%geoLatBu)
539  dealloc_(g%geoLonT) ; dealloc_(g%geoLonCu)
540  dealloc_(g%geoLonCv) ; dealloc_(g%geoLonBu)
541 
542  dealloc_(g%dx_Cv) ; dealloc_(g%dy_Cu)
543  dealloc_(g%dx_Cv_obc) ; dealloc_(g%dy_Cu_obc)
544 
545  dealloc_(g%bathyT) ; dealloc_(g%CoriolisBu)
546  dealloc_(g%dF_dx) ; dealloc_(g%dF_dy)
547  dealloc_(g%sin_rot) ; dealloc_(g%cos_rot)
548 
549  if (g%bathymetry_at_vel) then
550  dealloc_(g%Dblock_u) ; dealloc_(g%Dopen_u)
551  dealloc_(g%Dblock_v) ; dealloc_(g%Dopen_v)
552  endif
553 
554  deallocate(g%gridLonT) ; deallocate(g%gridLatT)
555  deallocate(g%gridLonB) ; deallocate(g%gridLatB)
556 
557  deallocate(g%Domain%mpp_domain)
558  deallocate(g%Domain)
559 
560 end subroutine mom_grid_end
561 
562 !> \namespace mom_grid
563 !!
564 !! Grid metrics and their inverses are labelled according to their staggered location on a Arakawa C (or B) grid.
565 !! - Metrics centered on h- or T-points are labelled T, e.g. dxT is the distance across the cell in the x-direction.
566 !! - Metrics centered on u-points are labelled Cu (C-grid u location). e.g. dyCu is the y-distance between two corners of a T-cell.
567 !! - Metrics centered on v-points are labelled Cv (C-grid v location). e.g. dyCv is the y-distance between two -points.
568 !! - Metrics centered on q-points are labelled Bu (B-grid u,v location). e.g. areaBu is the area centered on a q-point.
569 !!
570 !! \image html Grid_metrics.png "The labelling of distances (grid metrics) at various staggered location on an T-cell and around a q-point.
571 !!
572 !! Areas centered at T-, u-, v- and q- points are `areaT`, `areaCu`, `areaCv` and `areaBu` respectively.
573 !!
574 !! The reciprocal of metrics are pre-calculated and also stored in the ocean_grid_type with a I prepended to the name.
575 !! For example, `1./areaT` is called `IareaT`, and `1./dyCv` is `IdyCv`.
576 !!
577 !! Geographic latitude and longitude (or model coordinates if not on a sphere) are stored in `geoLatT`, `geoLonT` for T-points.
578 !! u-, v- and q- point coordinates are follow same pattern of replacing T with Cu, Cv and Bu respectively.
579 !!
580 !! Each location also has a 2D mask indicating whether the entire column is land or ocean.
581 !! `mask2dT` is 1 if the column is wet or 0 if the T-cell is land.
582 !! `mask2dCu` is 1 if both neighboring column are ocean, and 0 if either is land.
583 
584 end module mom_grid
subroutine, public mom_grid_init(G, param_file, HI, global_indexing, bathymetry_at_vel)
MOM_grid_init initializes the ocean grid array sizes and grid memory.
Definition: MOM_grid.F90:176
subroutine allocate_metrics(G)
Allocate memory used by the ocean_grid_type and related structures.
Definition: MOM_grid.F90:448
logical function, public ispointincell(G, i, j, x, y)
Returns true if the coordinates (x,y) are within the h-cell (i,j)
Definition: MOM_grid.F90:406
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public set_first_direction(G, y_first)
Definition: MOM_grid.F90:440
subroutine, public hor_index_init(Domain, HI, param_file, local_indexing, index_offset)
Sets various index values in a hor_index_type.
Defines the horizontal index type (hor_index_type) used for providing index ranges.
Container for horizontal index ranges for data, computational and global domains. ...
subroutine, public mom_grid_end(G)
Release memory used by the ocean_grid_type and related structures.
Definition: MOM_grid.F90:521
subroutine, public mom_mesg(message, verb, all_print)
The MOM_domain_type contains information about the domain decompositoin.
real function adcroft_reciprocal(val)
Adcroft_reciprocal(x) = 1/x for |x|>0 or 0 for x=0.
Definition: MOM_grid.F90:398
subroutine, public get_domain_extent(Domain, isc, iec, jsc, jec, isd, ied, jsd, jed, isg, ieg, jsg, jeg, idg_offset, jdg_offset, symmetric, local_indexing, index_offset)
subroutine, public set_derived_metrics(G)
set_derived_metrics calculates metric terms that are derived from other metrics.
Definition: MOM_grid.F90:353
subroutine, public mom_error(level, message, all_print)