11 implicit none ;
private 13 #include <MOM_memory.h> 60 logical :: nonblocking_updates
62 integer :: first_direction
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
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.
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.
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
121 real,
pointer,
dimension(:) :: &
122 gridlatt => null(), &
126 real,
pointer,
dimension(:) :: &
127 gridlont => null(), &
131 character(len=40) :: &
132 x_axis_units, & !< The units that are used in labeling the x coordinate axes.
135 real allocable_,
dimension(NIMEM_,NJMEM_) :: &
138 logical :: bathymetry_at_vel
141 real allocable_,
dimension(NIMEMB_PTR_,NJMEM_) :: &
142 dblock_u, & !< Topographic depths at u-points at which the flow is blocked, 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.
147 real allocable_,
dimension(NIMEMB_PTR_,NJMEMB_PTR_) :: &
149 real allocable_,
dimension(NIMEM_,NJMEM_) :: &
150 df_dx, & !< Derivative d/dx f (Coriolis parameter) at h-points, in s-1 m-1.
156 real :: iareat_global
168 real :: rad_earth = 6.378e6
175 subroutine mom_grid_init(G, param_file, HI, global_indexing, bathymetry_at_vel)
179 optional,
intent(in) :: HI
180 logical,
optional,
intent(in) :: global_indexing
183 logical,
optional,
intent(in) :: bathymetry_at_vel
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
197 integer,
allocatable,
dimension(:) :: ibegin, iend, jbegin, jend
198 character(len=40) :: mod_nm =
"MOM_grid" 203 "Parameters providing information about the lateral grid.")
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, &
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, &
213 if (
present(hi))
then 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
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
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
228 local_indexing = .true.
229 if (
present(global_indexing)) local_indexing = .not.global_indexing
231 local_indexing=local_indexing)
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
243 g%nonblocking_updates = g%Domain%nonblocking_updates
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
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
258 call mom_mesg(
" MOM_grid.F90, MOM_grid_init: allocating metrics", 5)
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
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
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")
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)
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")
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")
295 allocate(g%Block(nblocks))
296 ied_max = 1 ; jed_max = 1
301 i = mod((n-1), niblock) + 1
302 j = (n-1)/niblock + 1
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
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
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
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
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
331 ied_max = max(ied_max, g%Block(n)%ied)
332 jed_max = max(jed_max, g%Block(n)%jed)
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
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")
356 integer :: i, j, isd, ied, jsd, jed
357 integer :: IsdB, IedB, JsdB, JedB
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
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
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
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
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
391 if (g%areaBu(i,j) <= 0.0) g%areaBu(i,j) = g%dxBu(i,j) * g%dyBu(i,j)
398 real,
intent(in) :: val
401 i_val = 0.0 ;
if (val /= 0.0) i_val = 1.0/val
407 integer,
intent(in) :: i
408 integer,
intent(in) :: j
409 real,
intent(in) :: x
410 real,
intent(in) :: y
412 real :: xNE, xNW, xSE, xSW, yNE, yNW, ySE, ySW
413 real :: p0, p1, p2, p3, l0, l1, l2, l3
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)
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 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)
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.
434 if ( (abs(p0)+abs(p2)) + (abs(p1)+abs(p3)) == abs((p0+p2) + (p1+p3)) )
then 441 integer,
intent(in) :: y_first
443 g%first_direction = y_first
449 integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB, isg, ieg, jsg, jeg
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
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
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
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
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
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
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
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
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
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
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)
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)
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)
534 dealloc_(g%mask2dT) ; dealloc_(g%mask2dCu)
535 dealloc_(g%mask2dCv) ; dealloc_(g%mask2dBu)
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)
542 dealloc_(g%dx_Cv) ; dealloc_(g%dy_Cu)
543 dealloc_(g%dx_Cv_obc) ; dealloc_(g%dy_Cu_obc)
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)
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)
554 deallocate(g%gridLonT) ;
deallocate(g%gridLatT)
555 deallocate(g%gridLonB) ;
deallocate(g%gridLatB)
557 deallocate(g%Domain%mpp_domain)
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.
subroutine allocate_metrics(G)
Allocate memory used by the ocean_grid_type and related structures.
logical function, public ispointincell(G, i, j, x, y)
Returns true if the coordinates (x,y) are within the h-cell (i,j)
Ocean grid type. See mom_grid for details.
Provides the ocean grid type.
subroutine, public set_first_direction(G, y_first)
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.
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.
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.
subroutine, public mom_error(level, message, all_print)