MOM6
mom_grid_initialize Module Reference

Data Types

type  gps
 

Functions/Subroutines

subroutine, public set_grid_metrics (G, param_file)
 set_grid_metrics is used to set the primary values in the model's horizontal grid. The bathymetry, land-sea mask and any restricted channel widths are not known yet, so these are set later. More...
 
subroutine grid_metrics_chksum (parent, G)
 grid_metrics_chksum performs a set of checksums on metrics on the grid for debugging. More...
 
subroutine set_grid_metrics_from_mosaic (G, param_file)
 set_grid_metrics_from_mosaic sets the grid metrics from a mosaic file. More...
 
subroutine set_grid_metrics_cartesian (G, param_file)
 
subroutine set_grid_metrics_spherical (G, param_file)
 
subroutine set_grid_metrics_mercator (G, param_file)
 
real function ds_di (x, y, GP)
 
real function ds_dj (x, y, GP)
 
real function dl (x1, x2, y1, y2)
 
real function find_root (fn, dy_df, GP, fnval, y1, ymin, ymax, ittmax)
 
real function dx_di (x, GP)
 
real function int_di_dx (x, GP)
 
real function dy_dj (y, GP)
 
real function int_dj_dy (y, GP)
 
subroutine extrapolate_metric (var, jh, missing)
 extrapolate_metric extrapolates missing metric data into all the halo regions. More...
 
real function, public adcroft_reciprocal (val)
 This function implements Adcroft's rule for reciprocals, namely that Adcroft_Inv(x) = 1/x for |x|>0 or 0 for x=0. More...
 
subroutine, public initialize_masks (G, PF)
 initialize_masks initializes the grid masks and any metrics that come with masks already applied. More...
 

Function/Subroutine Documentation

◆ adcroft_reciprocal()

real function, public mom_grid_initialize::adcroft_reciprocal ( real, intent(in)  val)

This function implements Adcroft's rule for reciprocals, namely that Adcroft_Inv(x) = 1/x for |x|>0 or 0 for x=0.

Parameters
[in]valThe value being inverted.
Returns
The Adcroft reciprocal of val.

Definition at line 1279 of file MOM_grid_initialize.F90.

Referenced by initialize_masks().

1279  real, intent(in) :: val !< The value being inverted.
1280  real :: i_val !< The Adcroft reciprocal of val.
1281 
1282  i_val = 0.0
1283  if (val /= 0.0) i_val = 1.0/val
Here is the caller graph for this function:

◆ dl()

real function mom_grid_initialize::dl ( real, intent(in)  x1,
real, intent(in)  x2,
real, intent(in)  y1,
real, intent(in)  y2 
)
private

Definition at line 1013 of file MOM_grid_initialize.F90.

Referenced by set_grid_metrics_mercator().

1013  real, intent(in) :: x1, x2, y1, y2
1014  real :: dl
1015 ! This subroutine calculates the contribution from the line integral
1016 ! along one of the four sides of a cell face to the area of a cell,
1017 ! assuming that the sides follow a linear path in latitude and long-
1018 ! itude (i.e., on a Mercator grid).
1019 ! Argumnts: x1 - Segment starting longitude.
1020 ! (in) x2 - Segment ending longitude.
1021 ! (in) y1 - Segment ending latitude.
1022 ! (in) y2 - Segment ending latitude.
1023  real :: r, dy
1024 
1025  dy = y2 - y1
1026 
1027  if (abs(dy) > 2.5e-8) then
1028  r = ((1.0 - cos(dy))*cos(y1) + sin(dy)*sin(y1)) / dy
1029  else
1030  r = (0.5*dy*cos(y1) + sin(y1))
1031  endif
1032  dl = r * (x2 - x1)
1033 
Here is the caller graph for this function:

◆ ds_di()

real function mom_grid_initialize::ds_di ( real, intent(in)  x,
real, intent(in)  y,
type(gps), intent(in)  GP 
)
private

Definition at line 986 of file MOM_grid_initialize.F90.

References dx_di().

Referenced by set_grid_metrics_mercator().

986  real, intent(in) :: x, y
987  type(gps), intent(in) :: gp
988  real :: ds_di
989 ! This function returns the grid spacing in the logical x direction.
990 ! Arguments: x - The latitude in question.
991 ! (in) y - The longitude in question.
992  ds_di = gp%Rad_Earth * cos(y) * dx_di(x,gp)
993 ! In general, this might be...
994 ! ds_di = GP%Rad_Earth * sqrt( cos(y)*cos(y) * dx_di(x,y,GP)*dx_di(x,y,GP) + &
995 ! dy_di(x,y,GP)*dy_di(x,y,GP))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ds_dj()

real function mom_grid_initialize::ds_dj ( real, intent(in)  x,
real, intent(in)  y,
type(gps), intent(in)  GP 
)
private

Definition at line 999 of file MOM_grid_initialize.F90.

References dy_dj().

Referenced by set_grid_metrics_mercator().

999  real, intent(in) :: x, y
1000  type(gps), intent(in) :: gp
1001  real :: ds_dj
1002 ! This function returns the grid spacing in the logical y direction.
1003 ! Arguments: x - The latitude in question.
1004 ! (in) y - The longitude in question.
1005  ds_dj = gp%Rad_Earth * dy_dj(y,gp)
1006 ! In general, this might be...
1007 ! ds_dj = GP%Rad_Earth * sqrt( cos(y)*cos(y) * dx_dj(x,y,GP)*dx_dj(x,y,GP) + &
1008 ! dy_dj(x,y,GP)*dy_dj(x,y,GP))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ dx_di()

real function mom_grid_initialize::dx_di ( real, intent(in)  x,
type(gps), intent(in)  GP 
)
private

Definition at line 1146 of file MOM_grid_initialize.F90.

Referenced by ds_di(), and set_grid_metrics_mercator().

1146  real, intent(in) :: x
1147  type(gps), intent(in) :: gp
1148  real :: dx_di
1149 ! This subroutine calculates and returns the value of dx/di, where
1150 ! x is the longitude in Radians, and i is the integral north-south
1151 ! grid index.
1152 
1153  dx_di = (gp%len_lon * 4.0*atan(1.0)) / (180.0 * gp%niglobal)
1154 
Here is the caller graph for this function:

◆ dy_dj()

real function mom_grid_initialize::dy_dj ( real, intent(in)  y,
type(gps), intent(in)  GP 
)
private

Definition at line 1169 of file MOM_grid_initialize.F90.

Referenced by ds_dj(), and set_grid_metrics_mercator().

1169  real, intent(in) :: y
1170  type(gps), intent(in) :: gp
1171  real :: dy_dj
1172 ! This subroutine calculates and returns the value of dy/dj, where
1173 ! y is the latitude in Radians, and j is the integral north-south
1174 ! grid index.
1175  real :: pi ! 3.1415926... calculated as 4*atan(1)
1176  real :: c0 ! The constant that converts the nominal y-spacing in
1177  ! gridpoints to the nominal spacing in Radians.
1178  real :: y_eq_enhance ! The latitude in radians within which the resolution
1179  ! is enhanced.
1180  pi = 4.0*atan(1.0)
1181  if (gp%isotropic) then
1182  c0 = (gp%len_lon * pi) / (180.0 * gp%niglobal)
1183  y_eq_enhance = pi*abs(gp%lat_eq_enhance)/180.0
1184  if (abs(y) < y_eq_enhance) then
1185  dy_dj = c0 * (cos(y) / (1.0 + 0.5*cos(y) * (gp%lat_enhance_factor - 1.0) * &
1186  (1.0+cos(pi*y/y_eq_enhance)) ))
1187  else
1188  dy_dj = c0 * cos(y)
1189  endif
1190  else
1191  c0 = (gp%len_lat * pi) / (180.0 * gp%njglobal)
1192  dy_dj = c0
1193  endif
1194 
Here is the caller graph for this function:

◆ extrapolate_metric()

subroutine mom_grid_initialize::extrapolate_metric ( real, dimension(:,:), intent(inout)  var,
integer, intent(in)  jh,
real, intent(in), optional  missing 
)
private

extrapolate_metric extrapolates missing metric data into all the halo regions.

Parameters
[in,out]varThe array in which to fill in halos
[in]jhThe size of the halos to be filled
[in]missingThe missing data fill value, 0 by default.

Definition at line 1246 of file MOM_grid_initialize.F90.

Referenced by set_grid_metrics_from_mosaic().

1246  real, dimension(:,:), intent(inout) :: var !< The array in which to fill in halos
1247  integer, intent(in) :: jh !< The size of the halos to be filled
1248  real, optional, intent(in) :: missing !< The missing data fill value, 0 by default.
1249  real :: badval
1250  integer :: i,j
1251 
1252  badval = 0.0 ; if (present(missing)) badval = missing
1253 
1254  ! Fill in southern halo by extrapolating from the computational domain
1255  do j=lbound(var,2)+jh,lbound(var,2),-1 ; do i=lbound(var,1),ubound(var,1)
1256  if (var(i,j)==badval) var(i,j) = 2.0*var(i,j+1)-var(i,j+2)
1257  enddo ; enddo
1258 
1259  ! Fill in northern halo by extrapolating from the computational domain
1260  do j=ubound(var,2)-jh,ubound(var,2) ; do i=lbound(var,1),ubound(var,1)
1261  if (var(i,j)==badval) var(i,j) = 2.0*var(i,j-1)-var(i,j-2)
1262  enddo ; enddo
1263 
1264  ! Fill in western halo by extrapolating from the computational domain
1265  do j=lbound(var,2),ubound(var,2) ; do i=lbound(var,1)+jh,lbound(var,1),-1
1266  if (var(i,j)==badval) var(i,j) = 2.0*var(i+1,j)-var(i+2,j)
1267  enddo ; enddo
1268 
1269  ! Fill in eastern halo by extrapolating from the computational domain
1270  do j=lbound(var,2),ubound(var,2) ; do i=ubound(var,1)-jh,ubound(var,1)
1271  if (var(i,j)==badval) var(i,j) = 2.0*var(i-1,j)-var(i-2,j)
1272  enddo ; enddo
1273 
Here is the caller graph for this function:

◆ find_root()

real function mom_grid_initialize::find_root ( real, external  fn,
real, external  dy_df,
type(gps), intent(in)  GP,
real, intent(in)  fnval,
real, intent(in)  y1,
real, intent(in)  ymin,
real, intent(in)  ymax,
integer, intent(out)  ittmax 
)
private

Definition at line 1037 of file MOM_grid_initialize.F90.

Referenced by set_grid_metrics_mercator().

1037  real :: find_root
1038  real, external :: fn, dy_df
1039  type(gps), intent(in) :: gp
1040  real, intent(in) :: fnval, y1, ymin, ymax
1041  integer, intent(out) :: ittmax
1042  real :: y, y_next
1043 ! This subroutine finds and returns the value of y at which the
1044 ! monotonically increasing function fn takes the value fnval, also returning
1045 ! in ittmax the number of iterations of Newton's method that were
1046 ! used to polish the root.
1047  real :: ybot, ytop, fnbot, fntop
1048  integer :: itt
1049  character(len=256) :: warnmesg
1050 
1051  real :: dy_dfn, dy, fny
1052 
1053 ! Bracket the root. Do not use the bounding values because the value at the
1054 ! function at the bounds could be infinite, as is the case for the Mercator
1055 ! grid recursion relation. (I.e., this is a search on an open interval.)
1056  ybot = y1
1057  fnbot = fn(ybot,gp) - fnval ; itt = 0
1058  do while (fnbot > 0.0)
1059  if ((ybot - 2.0*dy_df(ybot,gp)) < (0.5*(ybot+ymin))) then
1060  ! Go twice as far as the secant method would normally go.
1061  ybot = ybot - 2.0*dy_df(ybot,gp)
1062  else ! But stay within the open interval!
1063  ybot = 0.5*(ybot+ymin) ; itt = itt + 1
1064  endif
1065  fnbot = fn(ybot,gp) - fnval
1066 
1067  if ((itt > 50) .and. (fnbot > 0.0)) then
1068  write(warnmesg, '("PE ",I2," unable to find bottom bound for grid function. &
1069  &x = ",ES10.4,", xmax = ",ES10.4,", fn = ",ES10.4,", dfn_dx = ",ES10.4,&
1070  &", seeking fn = ",ES10.4," - fn = ",ES10.4,".")') &
1071  pe_here(),ybot,ymin,fn(ybot,gp),dy_df(ybot,gp),fnval, fnbot
1072  call mom_error(fatal,warnmesg)
1073  endif
1074  enddo
1075 
1076  ytop = y1
1077  fntop = fn(ytop,gp) - fnval ; itt = 0
1078  do while (fntop < 0.0)
1079  if ((ytop + 2.0*dy_df(ytop,gp)) < (0.5*(ytop+ymax))) then
1080  ! Go twice as far as the secant method would normally go.
1081  ytop = ytop + 2.0*dy_df(ytop,gp)
1082  else ! But stay within the open interval!
1083  ytop = 0.5*(ytop+ymax) ; itt = itt + 1
1084  endif
1085  fntop = fn(ytop,gp) - fnval
1086 
1087  if ((itt > 50) .and. (fntop < 0.0)) then
1088  write(warnmesg, '("PE ",I2," unable to find top bound for grid function. &
1089  &x = ",ES10.4,", xmax = ",ES10.4,", fn = ",ES10.4,", dfn_dx = ",ES10.4, &
1090  &", seeking fn = ",ES10.4," - fn = ",ES10.4,".")') &
1091  pe_here(),ytop,ymax,fn(ytop,gp),dy_df(ytop,gp),fnval,fntop
1092  call mom_error(fatal,warnmesg)
1093  endif
1094  enddo
1095 
1096  ! Find the root using a bracketed variant of Newton's method, starting
1097  ! with a false-positon method first guess.
1098  if ((fntop < 0.0) .or. (fnbot > 0.0) .or. (ytop < ybot)) then
1099  write(warnmesg, '("PE ",I2," find_root failed to bracket function. y = ",&
1100  &2ES10.4,", fn = ",2ES10.4,".")') pe_here(),ybot,ytop,fnbot,fntop
1101  call mom_error(fatal, warnmesg)
1102  endif
1103 
1104  if (fntop == 0.0) then ; y = ytop ; fny = fntop
1105  elseif (fnbot == 0.0) then ; y = ybot ; fny = fnbot
1106  else
1107  y = (ybot*fntop - ytop*fnbot) / (fntop - fnbot)
1108  fny = fn(y,gp) - fnval
1109  if (fny < 0.0) then ; fnbot = fny ; ybot = y
1110  else ; fntop = fny ; ytop = y ; endif
1111  endif
1112 
1113  do itt=1,50
1114  dy_dfn = dy_df(y,gp)
1115 
1116  dy = -1.0* fny * dy_dfn
1117  y_next = y + dy
1118  if ((y_next >= ytop) .or. (y_next <= ybot)) then
1119  ! The Newton's method estimate has escaped bracketing, so use the
1120  ! false-position method instead. The complicated test is to properly
1121  ! handle the case where the iteration is down to roundoff level differences.
1122  y_next = y
1123  if (abs(fntop - fnbot) > epsilon(y) * (abs(fntop) + abs(fnbot))) &
1124  y_next = (ybot*fntop - ytop*fnbot) / (fntop - fnbot)
1125  endif
1126 
1127  dy = y_next - y
1128  if (abs(dy) < (2.0*epsilon(y)*(abs(y) + abs(y_next)) + 1.0e-20)) then
1129  y = y_next ; exit
1130  endif
1131  y = y_next
1132 
1133  fny = fn(y,gp) - fnval
1134  if (fny > 0.0) then ; ytop = y ; fntop = fny
1135  elseif (fny < 0.0) then ; ybot = y ; fnbot = fny
1136  else ; exit ; endif
1137 
1138  enddo
1139  if (abs(y) < 1e-12) y = 0.0
1140 
1141  ittmax = itt
1142  find_root = y
Here is the caller graph for this function:

◆ grid_metrics_chksum()

subroutine mom_grid_initialize::grid_metrics_chksum ( character(len=*), intent(in)  parent,
type(dyn_horgrid_type), intent(in)  G 
)
private

grid_metrics_chksum performs a set of checksums on metrics on the grid for debugging.

Parameters
[in]parentA string identifying the caller
[in]gThe dynamic horizontal grid type

Definition at line 170 of file MOM_grid_initialize.F90.

Referenced by set_grid_metrics().

170  character(len=*), intent(in) :: parent !< A string identifying the caller
171  type(dyn_horgrid_type), intent(in) :: g !< The dynamic horizontal grid type
172 
173  integer :: halo
174 
175  halo = min(g%ied-g%iec, g%jed-g%jec, 1)
176 
177  call hchksum_pair(trim(parent)//': d[xy]T', &
178  g%dxT, g%dyT, g%HI, haloshift=halo)
179 
180  call uvchksum(trim(parent)//': dxC[uv]', g%dxCu, g%dyCv, g%HI, haloshift=halo)
181 
182  call uvchksum(trim(parent)//': dxC[uv]', &
183  g%dyCu, g%dxCv, g%HI, haloshift=halo)
184 
185  call bchksum_pair(trim(parent)//': dxB[uv]', &
186  g%dxBu, g%dyBu, g%HI, haloshift=halo)
187 
188  call hchksum_pair(trim(parent)//': Id[xy]T', &
189  g%IdxT, g%IdyT, g%HI, haloshift=halo)
190 
191  call uvchksum(trim(parent)//': Id[xy]C[uv]', &
192  g%IdxCu, g%IdyCv, g%HI, haloshift=halo)
193 
194  call uvchksum(trim(parent)//': Id[xy]C[uv]', &
195  g%IdyCu, g%IdxCv, g%HI, haloshift=halo)
196 
197  call bchksum_pair(trim(parent)//': Id[xy]B[uv]', &
198  g%IdxBu, g%IdyBu, g%HI, haloshift=halo)
199 
200  call hchksum(g%areaT, trim(parent)//': areaT',g%HI, haloshift=halo)
201  call bchksum(g%areaBu, trim(parent)//': areaBu',g%HI, haloshift=halo)
202 
203  call hchksum(g%IareaT, trim(parent)//': IareaT',g%HI, haloshift=halo)
204  call bchksum(g%IareaBu, trim(parent)//': IareaBu',g%HI, haloshift=halo)
205 
206  call hchksum(g%geoLonT,trim(parent)//': geoLonT',g%HI, haloshift=halo)
207  call hchksum(g%geoLatT,trim(parent)//': geoLatT',g%HI, haloshift=halo)
208 
209  call bchksum(g%geoLonBu, trim(parent)//': geoLonBu',g%HI, haloshift=halo)
210  call bchksum(g%geoLatBu, trim(parent)//': geoLatBu',g%HI, haloshift=halo)
211 
212  call uvchksum(trim(parent)//': geoLonC[uv]', &
213  g%geoLonCu, g%geoLonCv, g%HI, haloshift=halo)
214 
215  call uvchksum(trim(parent)//': geoLatC[uv]', &
216  g%geoLatCu, g%geoLatCv, g%HI, haloshift=halo)
217 
Here is the caller graph for this function:

◆ initialize_masks()

subroutine, public mom_grid_initialize::initialize_masks ( type(dyn_horgrid_type), intent(inout)  G,
type(param_file_type), intent(in)  PF 
)

initialize_masks initializes the grid masks and any metrics that come with masks already applied.

Parameters
[in,out]gThe dynamic horizontal grid type
[in]pfParameter file structure

Definition at line 1289 of file MOM_grid_initialize.F90.

References adcroft_reciprocal().

Referenced by mom_fixed_initialization::mom_initialize_fixed().

1289  type(dyn_horgrid_type), intent(inout) :: g !< The dynamic horizontal grid type
1290  type(param_file_type), intent(in) :: pf !< Parameter file structure
1291 
1292 ! Initialize_masks sets mask2dT, mask2dCu, mask2dCv, and mask2dBu to mask out
1293 ! flow over any points which are shallower than Dmin and permit an
1294 ! appropriate treatment of the boundary conditions. mask2dCu and mask2dCv
1295 ! are 0.0 at any points adjacent to a land point. mask2dBu is 0.0 at
1296 ! any land or boundary point. For points in the interior, mask2dCu,
1297 ! mask2dCv, and mask2dBu are all 1.0.
1298 
1299  real :: dmin, min_depth, mask_depth
1300  character(len=40) :: mdl = "MOM_grid_init initialize_masks"
1301  integer :: i, j
1302 
1303  call calltree_enter("initialize_masks(), MOM_grid_initialize.F90")
1304  call get_param(pf, mdl, "MINIMUM_DEPTH", min_depth, &
1305  "If MASKING_DEPTH is unspecified, then anything shallower than\n"//&
1306  "MINIMUM_DEPTH is assumed to be land and all fluxes are masked out.\n"//&
1307  "If MASKING_DEPTH is specified, then all depths shallower than\n"//&
1308  "MINIMUM_DEPTH but deeper than MASKING_DEPTH are rounded to MINIMUM_DEPTH.", &
1309  units="m", default=0.0)
1310  call get_param(pf, mdl, "MASKING_DEPTH", mask_depth, &
1311  "The depth below which to mask points as land points, for which all\n"//&
1312  "fluxes are zeroed out. MASKING_DEPTH is ignored if negative.", &
1313  units="m", default=-9999.0)
1314 
1315  dmin = min_depth
1316  if (mask_depth>=0.) dmin = mask_depth
1317 
1318  g%mask2dCu(:,:) = 0.0 ; g%mask2dCv(:,:) = 0.0 ; g%mask2dBu(:,:) = 0.0
1319 
1320  ! Construct the h-point or T-point mask
1321  do j=g%jsd,g%jed ; do i=g%isd,g%ied
1322  if (g%bathyT(i,j) <= dmin) then
1323  g%mask2dT(i,j) = 0.0
1324  else
1325  g%mask2dT(i,j) = 1.0
1326  endif
1327  enddo ; enddo
1328 
1329  do j=g%jsd,g%jed ; do i=g%isd,g%ied-1
1330  if ((g%bathyT(i,j) <= dmin) .or. (g%bathyT(i+1,j) <= dmin)) then
1331  g%mask2dCu(i,j) = 0.0
1332  else
1333  g%mask2dCu(i,j) = 1.0
1334  endif
1335  enddo ; enddo
1336 
1337  do j=g%jsd,g%jed-1 ; do i=g%isd,g%ied
1338  if ((g%bathyT(i,j) <= dmin) .or. (g%bathyT(i,j+1) <= dmin)) then
1339  g%mask2dCv(i,j) = 0.0
1340  else
1341  g%mask2dCv(i,j) = 1.0
1342  endif
1343  enddo ; enddo
1344 
1345  do j=g%jsd,g%jed-1 ; do i=g%isd,g%ied-1
1346  if ((g%bathyT(i+1,j) <= dmin) .or. (g%bathyT(i+1,j+1) <= dmin) .or. &
1347  (g%bathyT(i,j) <= dmin) .or. (g%bathyT(i,j+1) <= dmin)) then
1348  g%mask2dBu(i,j) = 0.0
1349  else
1350  g%mask2dBu(i,j) = 1.0
1351  endif
1352  enddo ; enddo
1353 
1354  call pass_var(g%mask2dBu, g%Domain, position=corner)
1355  call pass_vector(g%mask2dCu, g%mask2dCv, g%Domain, to_all+scalar_pair, cgrid_ne)
1356 
1357  do j=g%jsd,g%jed ; do i=g%IsdB,g%IedB
1358  g%dy_Cu(i,j) = g%mask2dCu(i,j) * g%dyCu(i,j)
1359  g%dy_Cu_obc(i,j) = g%mask2dCu(i,j) * g%dyCu(i,j)
1360  g%areaCu(i,j) = g%dxCu(i,j) * g%dy_Cu(i,j)
1361  g%IareaCu(i,j) = g%mask2dCu(i,j) * adcroft_reciprocal(g%areaCu(i,j))
1362  enddo ; enddo
1363 
1364  do j=g%JsdB,g%JedB ; do i=g%isd,g%ied
1365  g%dx_Cv(i,j) = g%mask2dCv(i,j) * g%dxCv(i,j)
1366  g%dx_Cv_obc(i,j) = g%mask2dCv(i,j) * g%dxCv(i,j)
1367  g%areaCv(i,j) = g%dyCv(i,j) * g%dx_Cv(i,j)
1368  g%IareaCv(i,j) = g%mask2dCv(i,j) * adcroft_reciprocal(g%areaCv(i,j))
1369  enddo ; enddo
1370 
1371  call calltree_leave("initialize_masks()")
Here is the call graph for this function:
Here is the caller graph for this function:

◆ int_di_dx()

real function mom_grid_initialize::int_di_dx ( real, intent(in)  x,
type(gps), intent(in)  GP 
)
private

Definition at line 1158 of file MOM_grid_initialize.F90.

Referenced by set_grid_metrics_mercator().

1158  real, intent(in) :: x
1159  type(gps), intent(in) :: gp
1160  real :: int_di_dx
1161 ! This subroutine calculates and returns the integral of the inverse
1162 ! of dx/di to the point x, in radians.
1163 
1164  int_di_dx = x * ((180.0 * gp%niglobal) / (gp%len_lon * 4.0*atan(1.0)))
1165 
Here is the caller graph for this function:

◆ int_dj_dy()

real function mom_grid_initialize::int_dj_dy ( real, intent(in)  y,
type(gps), intent(in)  GP 
)
private

Definition at line 1198 of file MOM_grid_initialize.F90.

Referenced by set_grid_metrics_mercator().

1198  real, intent(in) :: y
1199  type(gps), intent(in) :: gp
1200  real :: int_dj_dy
1201 ! This subroutine calculates and returns the integral of the inverse
1202 ! of dy/dj to the point y, in radians.
1203  real :: i_c0 = 0.0 ! The inverse of the constant that converts the
1204  ! nominal spacing in gridpoints to the nominal
1205  ! spacing in Radians.
1206  real :: pi ! 3.1415926... calculated as 4*atan(1)
1207  real :: y_eq_enhance ! The latitude in radians from
1208  ! from the equator within which the
1209  ! meridional grid spacing is enhanced by
1210  ! a factor of GP%lat_enhance_factor.
1211  real :: r
1212 
1213  pi = 4.0*atan(1.0)
1214  if (gp%isotropic) then
1215  i_c0 = (180.0 * gp%niglobal) / (gp%len_lon * pi)
1216  y_eq_enhance = pi*abs(gp%lat_eq_enhance)/180.0
1217 
1218  if (y >= 0.0) then
1219  r = i_c0 * log((1.0 + sin(y))/cos(y))
1220  else
1221  r = -1.0 * i_c0 * log((1.0 - sin(y))/cos(y))
1222  endif
1223 
1224  if (y >= y_eq_enhance) then
1225  r = r + i_c0*0.5*(gp%lat_enhance_factor - 1.0)*y_eq_enhance
1226  else if (y <= -y_eq_enhance) then
1227  r = r - i_c0*0.5*(gp%lat_enhance_factor - 1.0)*y_eq_enhance
1228  else
1229  r = r + i_c0*0.5*(gp%lat_enhance_factor - 1.0) * &
1230  (y + (y_eq_enhance/pi)*sin(pi*y/y_eq_enhance))
1231  endif
1232  else
1233  i_c0 = (180.0 * gp%njglobal) / (gp%len_lat * pi)
1234  r = i_c0 * y
1235  endif
1236 
1237  int_dj_dy = r
Here is the caller graph for this function:

◆ set_grid_metrics()

subroutine, public mom_grid_initialize::set_grid_metrics ( type(dyn_horgrid_type), intent(inout)  G,
type(param_file_type), intent(in)  param_file 
)

set_grid_metrics is used to set the primary values in the model's horizontal grid. The bathymetry, land-sea mask and any restricted channel widths are not known yet, so these are set later.

Parameters
[in,out]gThe dynamic horizontal grid type
[in]param_fileParameter file structure

Definition at line 109 of file MOM_grid_initialize.F90.

References mom_error_handler::calltree_enter(), mom_error_handler::calltree_leave(), grid_metrics_chksum(), mom_dyn_horgrid::set_derived_dyn_horgrid(), set_grid_metrics_cartesian(), set_grid_metrics_from_mosaic(), set_grid_metrics_mercator(), and set_grid_metrics_spherical().

Referenced by mom_fixed_initialization::mom_initialize_fixed().

109  type(dyn_horgrid_type), intent(inout) :: g !< The dynamic horizontal grid type
110  type(param_file_type), intent(in) :: param_file !< Parameter file structure
111 ! Arguments:
112 ! (inout) G - The ocean's grid structure.
113 ! (in) param_file - A structure indicating the open file to parse for
114 ! model parameter values.
115 
116 ! Calculate the values of the metric terms that might be used
117 ! and save them in arrays.
118 ! Within this subroutine, the x- and y- grid spacings and their
119 ! inverses and the cell areas centered on h, q, u, and v points are
120 ! calculated, as are the geographic locations of each of these 4
121 ! sets of points.
122 ! This include declares and sets the variable "version".
123 #include "version_variable.h"
124  logical :: debug
125  character(len=256) :: config
126 
127  call calltree_enter("set_grid_metrics(), MOM_grid_initialize.F90")
128  call log_version(param_file, "MOM_grid_init", version, "")
129  call get_param(param_file, "MOM_grid_init", "GRID_CONFIG", config, &
130  "A character string that determines the method for \n"//&
131  "defining the horizontal grid. Current options are: \n"//&
132  " \t mosaic - read the grid from a mosaic (supergrid) \n"//&
133  " \t file set by GRID_FILE.\n"//&
134  " \t cartesian - use a (flat) Cartesian grid.\n"//&
135  " \t spherical - use a simple spherical grid.\n"//&
136  " \t mercator - use a Mercator spherical grid.", &
137  fail_if_missing=.true.)
138  call get_param(param_file, "MOM_grid_init", "DEBUG", debug, &
139  "If true, write out verbose debugging data.", default=.false.)
140 
141  ! These are defaults that may be changed in the next select block.
142  g%x_axis_units = "degrees_E" ; g%y_axis_units = "degrees_N"
143  select case (trim(config))
144  case ("mosaic"); call set_grid_metrics_from_mosaic(g, param_file)
145  case ("cartesian"); call set_grid_metrics_cartesian(g, param_file)
146  case ("spherical"); call set_grid_metrics_spherical(g, param_file)
147  case ("mercator"); call set_grid_metrics_mercator(g, param_file)
148  case ("file"); call mom_error(fatal, "MOM_grid_init: set_grid_metrics "//&
149  'GRID_CONFIG "file" is no longer a supported option. Use a '//&
150  'mosaic file ("mosaic") or one of the analytic forms instead.')
151  case default ; call mom_error(fatal, "MOM_grid_init: set_grid_metrics "//&
152  "Unrecognized grid configuration "//trim(config))
153  end select
154 
155 ! Calculate derived metrics (i.e. reciprocals and products)
156  call calltree_enter("set_derived_metrics(), MOM_grid_initialize.F90")
157  call set_derived_dyn_horgrid(g)
158  call calltree_leave("set_derived_metrics()")
159 
160  if (debug) call grid_metrics_chksum('MOM_grid_init/set_grid_metrics',g)
161 
162  call calltree_leave("set_grid_metrics()")
Here is the call graph for this function:
Here is the caller graph for this function:

◆ set_grid_metrics_cartesian()

subroutine mom_grid_initialize::set_grid_metrics_cartesian ( type(dyn_horgrid_type), intent(inout)  G,
type(param_file_type), intent(in)  param_file 
)
private
Parameters
[in,out]gThe dynamic horizontal grid type
[in]param_fileParameter file structure

Definition at line 465 of file MOM_grid_initialize.F90.

References mom_error_handler::calltree_enter(), and mom_error_handler::calltree_leave().

Referenced by set_grid_metrics().

465  type(dyn_horgrid_type), intent(inout) :: g !< The dynamic horizontal grid type
466  type(param_file_type), intent(in) :: param_file !< Parameter file structure
467 
468 ! Arguments:
469 ! (inout) G - The ocean's grid structure.
470 ! (in) param_file - A structure indicating the open file to parse for
471 ! model parameter values.
472 
473 ! Calculate the values of the metric terms for a Cartesian grid that
474 ! might be used and save them in arrays.
475 ! Within this subroutine, the x- and y- grid spacings and their
476 ! inverses and the cell areas centered on h, q, u, and v points are
477 ! calculated, as are the geographic locations of each of these 4
478 ! sets of points.
479  integer :: i, j, isd, ied, jsd, jed, isdb, iedb, jsdb, jedb, i1off, j1off
480  integer :: niglobal, njglobal
481  real :: grid_latt(g%jsd:g%jed), grid_latb(g%jsdb:g%jedb)
482  real :: grid_lont(g%isd:g%ied), grid_lonb(g%isdb:g%iedb)
483  real :: dx_everywhere, dy_everywhere ! Grid spacings in m.
484  real :: i_dx, i_dy ! Inverse grid spacings in m.
485  real :: pi
486  character(len=80) :: units_temp
487  character(len=48) :: mdl = "MOM_grid_init set_grid_metrics_cartesian"
488 
489  niglobal = g%Domain%niglobal ; njglobal = g%Domain%njglobal
490  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
491  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
492  i1off = g%idg_offset ; j1off = g%jdg_offset
493 
494  call calltree_enter("set_grid_metrics_cartesian(), MOM_grid_initialize.F90")
495 
496  pi = 4.0*atan(1.0) ;
497 
498  call get_param(param_file, mdl, "AXIS_UNITS", units_temp, &
499  "The units for the Cartesian axes. Valid entries are: \n"//&
500  " \t degrees - degrees of latitude and longitude \n"//&
501  " \t m - meters \n \t k - kilometers", default="degrees")
502  call get_param(param_file, mdl, "SOUTHLAT", g%south_lat, &
503  "The southern latitude of the domain or the equivalent \n"//&
504  "starting value for the y-axis.", units=units_temp, &
505  fail_if_missing=.true.)
506  call get_param(param_file, mdl, "LENLAT", g%len_lat, &
507  "The latitudinal or y-direction length of the domain.", &
508  units=units_temp, fail_if_missing=.true.)
509  call get_param(param_file, mdl, "WESTLON", g%west_lon, &
510  "The western longitude of the domain or the equivalent \n"//&
511  "starting value for the x-axis.", units=units_temp, &
512  default=0.0)
513  call get_param(param_file, mdl, "LENLON", g%len_lon, &
514  "The longitudinal or x-direction length of the domain.", &
515  units=units_temp, fail_if_missing=.true.)
516  call get_param(param_file, mdl, "RAD_EARTH", g%Rad_Earth, &
517  "The radius of the Earth.", units="m", default=6.378e6)
518 
519  if (units_temp(1:1) == 'k') then
520  g%x_axis_units = "kilometers" ; g%y_axis_units = "kilometers"
521  elseif (units_temp(1:1) == 'm') then
522  g%x_axis_units = "meters" ; g%y_axis_units = "meters"
523  endif
524  call log_param(param_file, mdl, "explicit AXIS_UNITS", g%x_axis_units)
525 
526  ! Note that the dynamic grid always uses symmetric memory for the global
527  ! arrays G%gridLatB and G%gridLonB.
528  do j=g%jsg-1,g%jeg
529  g%gridLatB(j) = g%south_lat + g%len_lat*REAL(j-(g%jsg-1))/REAL(njglobal)
530  enddo
531  do j=g%jsg,g%jeg
532  g%gridLatT(j) = g%south_lat + g%len_lat*(REAL(j-g%jsg)+0.5)/REAL(njglobal)
533  enddo
534  do i=g%isg-1,g%ieg
535  g%gridLonB(i) = g%west_lon + g%len_lon*REAL(i-(g%isg-1))/REAL(niglobal)
536  enddo
537  do i=g%isg,g%ieg
538  g%gridLonT(i) = g%west_lon + g%len_lon*(REAL(i-g%isg)+0.5)/REAL(niglobal)
539  enddo
540 
541  do j=jsdb,jedb
542  grid_latb(j) = g%south_lat + g%len_lat*REAL(j+j1off-(g%jsg-1))/REAL(njglobal)
543  enddo
544  do j=jsd,jed
545  grid_latt(j) = g%south_lat + g%len_lat*(REAL(j+j1off-g%jsg)+0.5)/REAL(njglobal)
546  enddo
547  do i=isdb,iedb
548  grid_lonb(i) = g%west_lon + g%len_lon*REAL(i+i1off-(g%isg-1))/REAL(niglobal)
549  enddo
550  do i=isd,ied
551  grid_lont(i) = g%west_lon + g%len_lon*(REAL(i+i1off-g%isg)+0.5)/REAL(niglobal)
552  enddo
553 
554  if (units_temp(1:1) == 'k') then ! Axes are measured in km.
555  dx_everywhere = 1000.0 * g%len_lon / (REAL(niglobal))
556  dy_everywhere = 1000.0 * g%len_lat / (REAL(njglobal))
557  else if (units_temp(1:1) == 'm') then ! Axes are measured in m.
558  dx_everywhere = g%len_lon / (REAL(niglobal))
559  dy_everywhere = g%len_lat / (REAL(njglobal))
560  else ! Axes are measured in degrees of latitude and longitude.
561  dx_everywhere = g%Rad_Earth * g%len_lon * pi / (180.0 * niglobal)
562  dy_everywhere = g%Rad_Earth * g%len_lat * pi / (180.0 * njglobal)
563  endif
564 
565  i_dx = 1.0 / dx_everywhere ; i_dy = 1.0 / dy_everywhere
566 
567  do j=jsdb,jedb ; do i=isdb,iedb
568  g%geoLonBu(i,j) = grid_lonb(i) ; g%geoLatBu(i,j) = grid_latb(j)
569 
570  g%dxBu(i,j) = dx_everywhere ; g%IdxBu(i,j) = i_dx
571  g%dyBu(i,j) = dy_everywhere ; g%IdyBu(i,j) = i_dy
572  g%areaBu(i,j) = dx_everywhere * dy_everywhere ; g%IareaBu(i,j) = i_dx * i_dy
573  enddo ; enddo
574 
575  do j=jsd,jed ; do i=isd,ied
576  g%geoLonT(i,j) = grid_lont(i) ; g%geoLatT(i,j) = grid_latt(j)
577  g%dxT(i,j) = dx_everywhere ; g%IdxT(i,j) = i_dx
578  g%dyT(i,j) = dy_everywhere ; g%IdyT(i,j) = i_dy
579  g%areaT(i,j) = dx_everywhere * dy_everywhere ; g%IareaT(i,j) = i_dx * i_dy
580  enddo ; enddo
581 
582  do j=jsd,jed ; do i=isdb,iedb
583  g%geoLonCu(i,j) = grid_lonb(i) ; g%geoLatCu(i,j) = grid_latt(j)
584 
585  g%dxCu(i,j) = dx_everywhere ; g%IdxCu(i,j) = i_dx
586  g%dyCu(i,j) = dy_everywhere ; g%IdyCu(i,j) = i_dy
587  enddo ; enddo
588 
589  do j=jsdb,jedb ; do i=isd,ied
590  g%geoLonCv(i,j) = grid_lont(i) ; g%geoLatCv(i,j) = grid_latb(j)
591 
592  g%dxCv(i,j) = dx_everywhere ; g%IdxCv(i,j) = i_dx
593  g%dyCv(i,j) = dy_everywhere ; g%IdyCv(i,j) = i_dy
594  enddo ; enddo
595 
596  call calltree_leave("set_grid_metrics_cartesian()")
Here is the call graph for this function:
Here is the caller graph for this function:

◆ set_grid_metrics_from_mosaic()

subroutine mom_grid_initialize::set_grid_metrics_from_mosaic ( type(dyn_horgrid_type), intent(inout)  G,
type(param_file_type), intent(in)  param_file 
)
private

set_grid_metrics_from_mosaic sets the grid metrics from a mosaic file.

Parameters
[in,out]gThe dynamic horizontal grid type
[in]param_fileParameter file structure

Definition at line 224 of file MOM_grid_initialize.F90.

References mom_error_handler::calltree_enter(), mom_error_handler::calltree_leave(), and extrapolate_metric().

Referenced by set_grid_metrics().

224  type(dyn_horgrid_type), intent(inout) :: g !< The dynamic horizontal grid type
225  type(param_file_type), intent(in) :: param_file !< Parameter file structure
226 ! This subroutine sets the grid metrics from a mosaic file.
227 !
228 ! Arguments:
229 ! (inout) G - The ocean's grid structure.
230 ! (in) param_file - A structure indicating the open file to parse for
231 ! model parameter values.
232 
233  real, dimension(G%isd :G%ied ,G%jsd :G%jed ) :: temph1, temph2, temph3, temph4
234  real, dimension(G%IsdB:G%IedB,G%JsdB:G%JedB) :: tempq1, tempq2, tempq3, tempq4
235  real, dimension(G%IsdB:G%IedB,G%jsd :G%jed ) :: tempe1, tempe2
236  real, dimension(G%isd :G%ied ,G%JsdB:G%JedB) :: tempn1, tempn2
237  ! These arrays are a holdover from earlier code in which the arrays in G were
238  ! macros and may have had reduced dimensions.
239  real, dimension(G%isd :G%ied ,G%jsd :G%jed ) :: dxt, dyt, areat
240  real, dimension(G%IsdB:G%IedB,G%jsd :G%jed ) :: dxcu, dycu
241  real, dimension(G%isd :G%ied ,G%JsdB:G%JedB) :: dxcv, dycv
242  real, dimension(G%IsdB:G%IedB,G%JsdB:G%JedB) :: dxbu, dybu, areabu
243  ! This are symmetric arrays, corresponding to the data in the mosaic file
244  real, dimension(2*G%isd-2:2*G%ied+1,2*G%jsd-2:2*G%jed+1) :: tmpt
245  real, dimension(2*G%isd-3:2*G%ied+1,2*G%jsd-2:2*G%jed+1) :: tmpu
246  real, dimension(2*G%isd-2:2*G%ied+1,2*G%jsd-3:2*G%jed+1) :: tmpv
247  real, dimension(2*G%isd-3:2*G%ied+1,2*G%jsd-3:2*G%jed+1) :: tmpz
248  real, dimension(:,:), allocatable :: tmpglbl
249  character(len=200) :: filename, grid_file, inputdir
250  character(len=64) :: mdl = "MOM_grid_init set_grid_metrics_from_mosaic"
251  integer :: err=0, ni, nj, global_indices(4)
252  type(mom_domain_type) :: sgdom ! Supergrid domain
253  integer :: i, j, i2, j2
254  integer :: npei,npej
255  integer, dimension(:), allocatable :: exni,exnj
256  integer :: start(4), nread(4)
257 
258  call calltree_enter("set_grid_metrics_from_mosaic(), MOM_grid_initialize.F90")
259 
260  call get_param(param_file, mdl, "GRID_FILE", grid_file, &
261  "Name of the file from which to read horizontal grid data.", &
262  fail_if_missing=.true.)
263  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
264  inputdir = slasher(inputdir)
265  filename = trim(adjustl(inputdir)) // trim(adjustl(grid_file))
266  call log_param(param_file, mdl, "INPUTDIR/GRID_FILE", filename)
267  if (.not.file_exists(filename)) &
268  call mom_error(fatal," set_grid_metrics_from_mosaic: Unable to open "//&
269  trim(filename))
270 
271 ! Initialize everything to 0.
272  dxcu(:,:) = 0.0 ; dycu(:,:) = 0.0
273  dxcv(:,:) = 0.0 ; dycv(:,:) = 0.0
274  dxbu(:,:) = 0.0 ; dybu(:,:) = 0.0 ; areabu(:,:) = 0.0
275 
276 !<MISSING CODE TO READ REFINEMENT LEVEL>
277  ni = 2*(g%iec-g%isc+1) ! i size of supergrid
278  nj = 2*(g%jec-g%jsc+1) ! j size of supergrid
279 
280 ! Define a domain for the supergrid (SGdom)
281  npei = g%domain%layout(1) ; npej = g%domain%layout(2)
282  allocate(exni(npei)) ; allocate(exnj(npej))
283  call mpp_get_domain_extents(g%domain%mpp_domain, exni, exnj)
284  allocate(sgdom%mpp_domain)
285  sgdom%nihalo = 2*g%domain%nihalo+1
286  sgdom%njhalo = 2*g%domain%njhalo+1
287  sgdom%niglobal = 2*g%domain%niglobal
288  sgdom%njglobal = 2*g%domain%njglobal
289  sgdom%layout(:) = g%domain%layout(:)
290  sgdom%use_io_layout = g%domain%use_io_layout
291  sgdom%io_layout(:) = g%domain%io_layout(:)
292  global_indices(1) = 1+sgdom%nihalo
293  global_indices(2) = sgdom%niglobal+sgdom%nihalo
294  global_indices(3) = 1+sgdom%njhalo
295  global_indices(4) = sgdom%njglobal+sgdom%njhalo
296  exni(:) = 2*exni(:) ; exnj(:) = 2*exnj(:)
297  if(ASSOCIATED(g%domain%maskmap)) then
298  call mom_define_domain(global_indices, sgdom%layout, sgdom%mpp_domain, &
299  xflags=g%domain%X_FLAGS, yflags=g%domain%Y_FLAGS, &
300  xhalo=sgdom%nihalo, yhalo=sgdom%njhalo, &
301  xextent=exni,yextent=exnj, &
302  symmetry=.true., name="MOM_MOSAIC", maskmap=g%domain%maskmap)
303  else
304  call mom_define_domain(global_indices, sgdom%layout, sgdom%mpp_domain, &
305  xflags=g%domain%X_FLAGS, yflags=g%domain%Y_FLAGS, &
306  xhalo=sgdom%nihalo, yhalo=sgdom%njhalo, &
307  xextent=exni,yextent=exnj, &
308  symmetry=.true., name="MOM_MOSAIC")
309  endif
310 
311  if (sgdom%use_io_layout) &
312  call mom_define_io_domain(sgdom%mpp_domain, sgdom%io_layout)
313  deallocate(exni)
314  deallocate(exnj)
315 
316 ! Read X from the supergrid
317  tmpz(:,:) = 999.
318  call read_data(filename, 'x', tmpz, domain=sgdom%mpp_domain, position=corner)
319 
320  call pass_var(tmpz, sgdom, position=corner)
321  call extrapolate_metric(tmpz, 2*(g%jsc-g%jsd)+2, missing=999.)
322  do j=g%jsd,g%jed ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
323  g%geoLonT(i,j) = tmpz(i2-1,j2-1)
324  enddo ; enddo
325  do j=g%JsdB,g%JedB ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
326  g%geoLonBu(i,j) = tmpz(i2,j2)
327  enddo ; enddo
328  do j=g%jsd,g%jed ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
329  g%geoLonCu(i,j) = tmpz(i2,j2-1)
330  enddo ; enddo
331  do j=g%JsdB,g%JedB ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
332  g%geoLonCv(i,j) = tmpz(i2-1,j2)
333  enddo ; enddo
334  ! For some reason, this messes up the solution...
335  ! call pass_var(G%geoLonBu, G%domain, position=CORNER)
336 
337 ! Read Y from the supergrid
338  tmpz(:,:) = 999.
339  call read_data(filename, 'y', tmpz, domain=sgdom%mpp_domain, position=corner)
340 
341  call pass_var(tmpz, sgdom, position=corner)
342  call extrapolate_metric(tmpz, 2*(g%jsc-g%jsd)+2, missing=999.)
343  do j=g%jsd,g%jed ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
344  g%geoLatT(i,j) = tmpz(i2-1,j2-1)
345  enddo ; enddo
346  do j=g%JsdB,g%JedB ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
347  g%geoLatBu(i,j) = tmpz(i2,j2)
348  enddo ; enddo
349  do j=g%jsd,g%jed ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
350  g%geoLatCu(i,j) = tmpz(i2,j2-1)
351  enddo ; enddo
352  do j=g%JsdB,g%JedB ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
353  g%geoLatCv(i,j) = tmpz(i2-1,j2)
354  enddo ; enddo
355 
356 ! Read DX,DY from the supergrid
357  tmpu(:,:) = 0. ; tmpv(:,:) = 0.
358  call read_data(filename,'dx',tmpv,domain=sgdom%mpp_domain,position=north_face)
359  call read_data(filename,'dy',tmpu,domain=sgdom%mpp_domain,position=east_face)
360  call pass_vector(tmpu, tmpv, sgdom, to_all+scalar_pair, cgrid_ne)
361  call extrapolate_metric(tmpv, 2*(g%jsc-g%jsd)+2, missing=0.)
362  call extrapolate_metric(tmpu, 2*(g%jsc-g%jsd)+2, missing=0.)
363 
364  do j=g%jsd,g%jed ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
365  dxt(i,j) = tmpv(i2-1,j2-1) + tmpv(i2,j2-1)
366  dyt(i,j) = tmpu(i2-1,j2-1) + tmpu(i2-1,j2)
367  enddo ; enddo
368 
369  do j=g%jsd,g%jed ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
370  dxcu(i,j) = tmpv(i2,j2-1) + tmpv(i2+1,j2-1)
371  dycu(i,j) = tmpu(i2,j2-1) + tmpu(i2,j2)
372  enddo ; enddo
373 
374  do j=g%JsdB,g%JedB ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
375  dxcv(i,j) = tmpv(i2-1,j2) + tmpv(i2,j2)
376  dycv(i,j) = tmpu(i2-1,j2) + tmpu(i2-1,j2+1)
377  enddo ; enddo
378 
379  do j=g%JsdB,g%JedB ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
380  dxbu(i,j) = tmpv(i2,j2) + tmpv(i2+1,j2)
381  dybu(i,j) = tmpu(i2,j2) + tmpu(i2,j2+1)
382  enddo ; enddo
383 
384 ! Read AREA from the supergrid
385  tmpt(:,:) = 0.
386  call read_data(filename, 'area', tmpt, domain=sgdom%mpp_domain)
387  call pass_var(tmpt, sgdom)
388  call extrapolate_metric(tmpt, 2*(g%jsc-g%jsd)+2, missing=0.)
389 
390  do j=g%jsd,g%jed ; do i=g%isd,g%ied ; i2 = 2*i ; j2 = 2*j
391  areat(i,j) = (tmpt(i2-1,j2-1) + tmpt(i2,j2)) + &
392  (tmpt(i2-1,j2) + tmpt(i2,j2-1))
393  enddo ; enddo
394  do j=g%JsdB,g%JedB ; do i=g%IsdB,g%IedB ; i2 = 2*i ; j2 = 2*j
395  areabu(i,j) = (tmpt(i2,j2) + tmpt(i2+1,j2+1)) + &
396  (tmpt(i2,j2+1) + tmpt(i2+1,j2))
397  enddo ; enddo
398 
399  ni=sgdom%niglobal
400  nj=sgdom%njglobal
401  call mpp_deallocate_domain(sgdom%mpp_domain)
402  deallocate(sgdom%mpp_domain)
403 
404  call pass_vector(dycu, dxcv, g%Domain, to_all+scalar_pair, cgrid_ne)
405  call pass_vector(dxcu, dycv, g%Domain, to_all+scalar_pair, cgrid_ne)
406  call pass_vector(dxbu, dybu, g%Domain, to_all+scalar_pair, bgrid_ne)
407  call pass_var(areat, g%Domain)
408  call pass_var(areabu, g%Domain, position=corner)
409 
410  do i=g%isd,g%ied ; do j=g%jsd,g%jed
411  g%dxT(i,j) = dxt(i,j) ; g%dyT(i,j) = dyt(i,j) ; g%areaT(i,j) = areat(i,j)
412  enddo ; enddo
413  do i=g%IsdB,g%IedB ; do j=g%jsd,g%jed
414  g%dxCu(i,j) = dxcu(i,j) ; g%dyCu(i,j) = dycu(i,j)
415  enddo ; enddo
416  do i=g%isd,g%ied ; do j=g%JsdB,g%JedB
417  g%dxCv(i,j) = dxcv(i,j) ; g%dyCv(i,j) = dycv(i,j)
418  enddo ; enddo
419  do i=g%IsdB,g%IedB ; do j=g%JsdB,g%JedB
420  g%dxBu(i,j) = dxbu(i,j) ; g%dyBu(i,j) = dybu(i,j) ; g%areaBu(i,j) = areabu(i,j)
421  enddo ; enddo
422 
423  ! Construct axes for diagnostic output (only necessary because "ferret" uses
424  ! broken convention for interpretting netCDF files).
425  start(:) = 1 ; nread(:) = 1
426  start(2) = 2 ; nread(1) = ni+1 ; nread(2) = 2
427  allocate( tmpglbl(ni+1,2) )
428  if (is_root_pe()) &
429  call read_data(filename, "x", tmpglbl, start, nread, no_domain=.true.)
430  call broadcast(tmpglbl, 2*(ni+1), root_pe())
431 
432  ! I don't know why the second axis is 1 or 2 here. -RWH
433  do i=g%isg,g%ieg
434  g%gridLonT(i) = tmpglbl(2*(i-g%isg)+2,2)
435  enddo
436  ! Note that the dynamic grid always uses symmetric memory for the global
437  ! arrays G%gridLatB and G%gridLonB.
438  do i=g%isg-1,g%ieg
439  g%gridLonB(i) = tmpglbl(2*(i-g%isg)+3,1)
440  enddo
441  deallocate( tmpglbl )
442 
443  allocate( tmpglbl(1, nj+1) )
444  start(:) = 1 ; nread(:) = 1
445  start(1) = int(ni/4)+1 ; nread(2) = nj+1
446  if (is_root_pe()) &
447  call read_data(filename, "y", tmpglbl, start, nread, no_domain=.true.)
448  call broadcast(tmpglbl, nj+1, root_pe())
449 
450  do j=g%jsg,g%jeg
451  g%gridLatT(j) = tmpglbl(1,2*(j-g%jsg)+2)
452  enddo
453  do j=g%jsg-1,g%jeg
454  g%gridLatB(j) = tmpglbl(1,2*(j-g%jsg)+3)
455  enddo
456  deallocate( tmpglbl )
457 
458  call calltree_leave("set_grid_metrics_from_mosaic()")
Here is the call graph for this function:
Here is the caller graph for this function:

◆ set_grid_metrics_mercator()

subroutine mom_grid_initialize::set_grid_metrics_mercator ( type(dyn_horgrid_type), intent(inout)  G,
type(param_file_type), intent(in)  param_file 
)
private
Parameters
[in,out]gThe dynamic horizontal grid type
[in]param_fileParameter file structure

Definition at line 744 of file MOM_grid_initialize.F90.

References dl(), ds_di(), ds_dj(), dx_di(), dy_dj(), find_root(), int_di_dx(), and int_dj_dy().

Referenced by set_grid_metrics().

744  type(dyn_horgrid_type), intent(inout) :: g !< The dynamic horizontal grid type
745  type(param_file_type), intent(in) :: param_file !< Parameter file structure
746 
747 ! Arguments:
748 ! (inout) G - The ocean's grid structure.
749 ! (in) param_file - A structure indicating the open file to parse for
750 ! model parameter values.
751 
752 ! Calculate the values of the metric terms that might be used
753 ! and save them in arrays.
754 ! Within this subroutine, the x- and y- grid spacings and their
755 ! inverses and the cell areas centered on h, q, u, and v points are
756 ! calculated, as are the geographic locations of each of these 4
757 ! sets of points.
758  integer :: i, j, isd, ied, jsd, jed
759  integer :: i_off, j_off
760  type(gps) :: gp
761  character(len=128) :: warnmesg
762  character(len=48) :: mdl = "MOM_grid_init set_grid_metrics_mercator"
763  real :: pi, pi_2! PI = 3.1415926... as 4*atan(1), PI_2 = (PI) /2.0
764 
765 
766 ! All of the metric terms should be defined over the domain from
767 ! isd to ied. Outside of the physical domain, both the metrics
768 ! and their inverses may be set to zero.
769 
770 ! The metric terms within the computational domain are set here.
771  real :: y_q, y_h, jd, x_q, x_h, id
772  real, dimension(G%isd:G%ied,G%jsd:G%jed) :: &
773  xh, yh ! Latitude and longitude of h points in radians.
774  real, dimension(G%IsdB:G%IedB,G%jsd:G%jed) :: &
775  xu, yu ! Latitude and longitude of u points in radians.
776  real, dimension(G%isd:G%ied,G%JsdB:G%JedB) :: &
777  xv, yv ! Latitude and longitude of v points in radians.
778  real, dimension(G%IsdB:G%IedB,G%JsdB:G%JedB) :: &
779  xq, yq ! Latitude and longitude of q points in radians.
780  real :: fnref ! fnRef is the value of Int_dj_dy or
781  ! Int_dj_dy at a latitude or longitude that is
782  real :: jref, iref ! being set to be at grid index jRef or iRef.
783  integer :: itt1, itt2
784  logical :: debug = .false., simple_area = .true.
785  integer :: is, ie, js, je, isq, ieq, jsq, jeq, isdb, iedb, jsdb, jedb
786 
787  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
788  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
789  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
790  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
791  i_off = g%idg_offset ; j_off = g%jdg_offset
792 
793  gp%niglobal = g%Domain%niglobal
794  gp%njglobal = g%Domain%njglobal
795 
796  call calltree_enter("set_grid_metrics_mercator(), MOM_grid_initialize.F90")
797 
798 ! Calculate the values of the metric terms that might be used
799 ! and save them in arrays.
800  pi = 4.0*atan(1.0) ; pi_2 = 0.5*pi
801 
802  call get_param(param_file, mdl, "SOUTHLAT", gp%south_lat, &
803  "The southern latitude of the domain.", units="degrees", &
804  fail_if_missing=.true.)
805  call get_param(param_file, mdl, "LENLAT", gp%len_lat, &
806  "The latitudinal length of the domain.", units="degrees", &
807  fail_if_missing=.true.)
808  call get_param(param_file, mdl, "WESTLON", gp%west_lon, &
809  "The western longitude of the domain.", units="degrees", &
810  default=0.0)
811  call get_param(param_file, mdl, "LENLON", gp%len_lon, &
812  "The longitudinal length of the domain.", units="degrees", &
813  fail_if_missing=.true.)
814  call get_param(param_file, mdl, "RAD_EARTH", gp%Rad_Earth, &
815  "The radius of the Earth.", units="m", default=6.378e6)
816  g%south_lat = gp%south_lat ; g%len_lat = gp%len_lat
817  g%west_lon = gp%west_lon ; g%len_lon = gp%len_lon
818  g%Rad_Earth = gp%Rad_Earth
819  call get_param(param_file, mdl, "ISOTROPIC", gp%isotropic, &
820  "If true, an isotropic grid on a sphere (also known as \n"//&
821  "a Mercator grid) is used. With an isotropic grid, the \n"//&
822  "meridional extent of the domain (LENLAT), the zonal \n"//&
823  "extent (LENLON), and the number of grid points in each \n"//&
824  "direction are _not_ independent. In MOM the meridional \n"//&
825  "extent is determined to fit the zonal extent and the \n"//&
826  "number of grid points, while grid is perfectly isotropic.", &
827  default=.false.)
828  call get_param(param_file, mdl, "EQUATOR_REFERENCE", gp%equator_reference, &
829  "If true, the grid is defined to have the equator at the \n"//&
830  "nearest q- or h- grid point to (-LOWLAT*NJGLOBAL/LENLAT).", &
831  default=.true.)
832  call get_param(param_file, mdl, "LAT_ENHANCE_FACTOR", gp%Lat_enhance_factor, &
833  "The amount by which the meridional resolution is \n"//&
834  "enhanced within LAT_EQ_ENHANCE of the equator.", &
835  units="nondim", default=1.0)
836  call get_param(param_file, mdl, "LAT_EQ_ENHANCE", gp%Lat_eq_enhance, &
837  "The latitude range to the north and south of the equator \n"//&
838  "over which the resolution is enhanced.", units="degrees", &
839  default=0.0)
840 
841 ! With an isotropic grid, the north-south extent of the domain,
842 ! the east-west extent, and the number of grid points in each
843 ! direction are _not_ independent. Here the north-south extent
844 ! will be determined to fit the east-west extent and the number of
845 ! grid points. The grid is perfectly isotropic.
846  if (gp%equator_reference) then
847 ! With the following expression, the equator will always be placed
848 ! on either h or q points, in a position consistent with the ratio
849 ! GP%south_lat to GP%len_lat.
850  jref = (g%jsg-1) + 0.5*floor(gp%njglobal*((-1.0*gp%south_lat*2.0)/gp%len_lat)+0.5)
851  fnref = int_dj_dy(0.0, gp)
852  else
853 ! The following line sets the reference latitude GP%south_lat at j=js-1 (or -2?)
854  jref = (g%jsg-1)
855  fnref = int_dj_dy((gp%south_lat*pi/180.0), gp)
856  endif
857 
858  ! These calculations no longer depend on the the order in which they
859  ! are performed because they all use the same (poor) starting guess and
860  ! iterate to convergence.
861  ! Note that the dynamic grid always uses symmetric memory for the global
862  ! arrays G%gridLatB and G%gridLonB.
863  do j=g%jsg-1,g%jeg
864  jd = fnref + (j - jref)
865  y_q = find_root(int_dj_dy, dy_dj, gp, jd, 0.0, -1.0*pi_2, pi_2, itt2)
866  g%gridLatB(j) = y_q*180.0/pi
867  ! if (is_root_pe()) &
868  ! write(*, '("J, y_q = ",I4,ES14.4," itts = ",I4)') j, y_q, itt2
869  enddo
870  do j=g%jsg,g%jeg
871  jd = fnref + (j - jref) - 0.5
872  y_h = find_root(int_dj_dy, dy_dj, gp, jd, 0.0, -1.0*pi_2, pi_2, itt1)
873  g%gridLatT(j) = y_h*180.0/pi
874  ! if (is_root_pe()) &
875  ! write(*, '("j, y_h = ",I4,ES14.4," itts = ",I4)') j, y_h, itt1
876  enddo
877  do j=jsdb+j_off,jedb+j_off
878  jd = fnref + (j - jref)
879  y_q = find_root(int_dj_dy, dy_dj, gp, jd, 0.0, -1.0*pi_2, pi_2, itt2)
880  do i=isdb,iedb ; yq(i,j-j_off) = y_q ; enddo
881  do i=isd,ied ; yv(i,j-j_off) = y_q ; enddo
882  enddo
883  do j=jsd+j_off,jed+j_off
884  jd = fnref + (j - jref) - 0.5
885  y_h = find_root(int_dj_dy, dy_dj, gp, jd, 0.0, -1.0*pi_2, pi_2, itt1)
886  if ((j >= jsd+j_off) .and. (j <= jed+j_off)) then
887  do i=isd,ied ; yh(i,j-j_off) = y_h ; enddo
888  do i=isdb,iedb ; yu(i,j-j_off) = y_h ; enddo
889  endif
890  enddo
891 
892 ! Determine the longitudes of the various points.
893 
894 ! These two lines place the western edge of the domain at GP%west_lon.
895  iref = (g%isg-1) + gp%niglobal
896  fnref = int_di_dx(((gp%west_lon+gp%len_lon)*pi/180.0), gp)
897 
898  ! These calculations no longer depend on the the order in which they
899  ! are performed because they all use the same (poor) starting guess and
900  ! iterate to convergence.
901  do i=g%isg-1,g%ieg
902  id = fnref + (i - iref)
903  x_q = find_root(int_di_dx, dx_di, gp, id, 0.0, -4.0*pi, 4.0*pi, itt2)
904  g%gridLonB(i) = x_q*180.0/pi
905  enddo
906  do i=g%isg,g%ieg
907  id = fnref + (i - iref) - 0.5
908  x_h = find_root(int_di_dx, dx_di, gp, id, 0.0, -4.0*pi, 4.0*pi, itt1)
909  g%gridLonT(i) = x_h*180.0/pi
910  enddo
911  do i=isdb+i_off,iedb+i_off
912  id = fnref + (i - iref)
913  x_q = find_root(int_di_dx, dx_di, gp, id, 0.0, -4.0*pi, 4.0*pi, itt2)
914  do j=jsdb,jedb ; xq(i-i_off,j) = x_q ; enddo
915  do j=jsd,jed ; xu(i-i_off,j) = x_q ; enddo
916  enddo
917  do i=isd+i_off,ied+i_off
918  id = fnref + (i - iref) - 0.5
919  x_h = find_root(int_di_dx, dx_di, gp, id, 0.0, -4.0*pi, 4.0*pi, itt1)
920  do j=jsd,jed ; xh(i-i_off,j) = x_h ; enddo
921  do j=jsdb,jedb ; xv(i-i_off,j) = x_h ; enddo
922  enddo
923 
924  do j=jsdb,jedb ; do i=isdb,iedb
925  g%geoLonBu(i,j) = xq(i,j)*180.0/pi
926  g%geoLatBu(i,j) = yq(i,j)*180.0/pi
927  g%dxBu(i,j) = ds_di(xq(i,j), yq(i,j), gp)
928  g%dyBu(i,j) = ds_dj(xq(i,j), yq(i,j), gp)
929 
930  g%areaBu(i,j) = g%dxBu(i,j) * g%dyBu(i,j)
931  g%IareaBu(i,j) = 1.0 / g%areaBu(i,j)
932  enddo ; enddo
933 
934  do j=jsd,jed ; do i=isd,ied
935  g%geoLonT(i,j) = xh(i,j)*180.0/pi
936  g%geoLatT(i,j) = yh(i,j)*180.0/pi
937  g%dxT(i,j) = ds_di(xh(i,j), yh(i,j), gp)
938  g%dyT(i,j) = ds_dj(xh(i,j), yh(i,j), gp)
939 
940  g%areaT(i,j) = g%dxT(i,j)*g%dyT(i,j)
941  g%IareaT(i,j) = 1.0 / g%areaT(i,j)
942  enddo ; enddo
943 
944  do j=jsd,jed ; do i=isdb,iedb
945  g%geoLonCu(i,j) = xu(i,j)*180.0/pi
946  g%geoLatCu(i,j) = yu(i,j)*180.0/pi
947  g%dxCu(i,j) = ds_di(xu(i,j), yu(i,j), gp)
948  g%dyCu(i,j) = ds_dj(xu(i,j), yu(i,j), gp)
949  enddo ; enddo
950 
951  do j=jsdb,jedb ; do i=isd,ied
952  g%geoLonCv(i,j) = xv(i,j)*180.0/pi
953  g%geoLatCv(i,j) = yv(i,j)*180.0/pi
954  g%dxCv(i,j) = ds_di(xv(i,j), yv(i,j), gp)
955  g%dyCv(i,j) = ds_dj(xv(i,j), yv(i,j), gp)
956  enddo ; enddo
957 
958  if (.not.simple_area) then
959  do j=jsdb+1,jed ; do i=isdb+1,ied
960  g%areaT(i,j) = gp%Rad_Earth**2 * &
961  (dl(xq(i-1,j-1),xq(i-1,j),yq(i-1,j-1),yq(i-1,j)) + &
962  (dl(xq(i-1,j),xq(i,j),yq(i-1,j),yq(i,j)) + &
963  (dl(xq(i,j),xq(i,j-1),yq(i,j),yq(i,j-1)) + &
964  dl(xq(i,j-1),xq(i-1,j-1),yq(i,j-1),yq(i-1,j-1)))))
965  enddo ;enddo
966  if ((isdb == isd) .or. (jsdb == jsq)) then
967  ! Fill in row and column 1 to calculate the area in the southernmost
968  ! and westernmost land cells when we are not using symmetric memory.
969  ! The pass_var call updates these values if they are not land cells.
970  g%areaT(isd+1,jsd) = g%areaT(isd+1,jsd+1)
971  do j=jsd,jed ; g%areaT(isd,j) = g%areaT(isd+1,j) ; enddo
972  do i=isd,ied ; g%areaT(i,jsd) = g%areaT(i,jsd+1) ; enddo
973  ! Now replace the data in the halos, if value values exist.
974  call pass_var(g%areaT,g%Domain)
975  endif
976  do j=jsd,jed ; do i=isd,ied
977  g%IareaT(i,j) = 1.0 / g%areaT(i,j)
978  enddo ; enddo
979  endif
980 
981  call calltree_leave("set_grid_metrics_mercator()")
Here is the call graph for this function:
Here is the caller graph for this function:

◆ set_grid_metrics_spherical()

subroutine mom_grid_initialize::set_grid_metrics_spherical ( type(dyn_horgrid_type), intent(inout)  G,
type(param_file_type), intent(in)  param_file 
)
private
Parameters
[in,out]gThe dynamic horizontal grid type
[in]param_fileParameter file structure

Definition at line 602 of file MOM_grid_initialize.F90.

References mom_error_handler::calltree_enter().

Referenced by set_grid_metrics().

602  type(dyn_horgrid_type), intent(inout) :: g !< The dynamic horizontal grid type
603  type(param_file_type), intent(in) :: param_file !< Parameter file structure
604 
605 ! Arguments:
606 ! (inout) G - The ocean's grid structure.
607 ! (in) param_file - A structure indicating the open file to parse for
608 ! model parameter values.
609 
610 ! Calculate the values of the metric terms that might be used
611 ! and save them in arrays.
612 ! Within this subroutine, the x- and y- grid spacings and their
613 ! inverses and the cell areas centered on h, q, u, and v points are
614 ! calculated, as are the geographic locations of each of these 4
615 ! sets of points.
616  real :: pi, pi_180! PI = 3.1415926... as 4*atan(1)
617  integer :: i, j, isd, ied, jsd, jed
618  integer :: is, ie, js, je, isq, ieq, jsq, jeq, isdb, iedb, jsdb, jedb
619  integer :: i_offset, j_offset
620  real :: grid_latt(g%jsd:g%jed), grid_latb(g%jsdb:g%jedb)
621  real :: grid_lont(g%isd:g%ied), grid_lonb(g%isdb:g%iedb)
622  real :: dlon,dlat,latitude,longitude,dl_di
623  character(len=48) :: mdl = "MOM_grid_init set_grid_metrics_spherical"
624 
625  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
626  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
627  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
628  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
629  i_offset = g%idg_offset ; j_offset = g%jdg_offset
630 
631  call calltree_enter("set_grid_metrics_spherical(), MOM_grid_initialize.F90")
632 
633 ! Calculate the values of the metric terms that might be used
634 ! and save them in arrays.
635  pi = 4.0*atan(1.0); pi_180 = atan(1.0)/45.
636 
637  call get_param(param_file, mdl, "SOUTHLAT", g%south_lat, &
638  "The southern latitude of the domain.", units="degrees", &
639  fail_if_missing=.true.)
640  call get_param(param_file, mdl, "LENLAT", g%len_lat, &
641  "The latitudinal length of the domain.", units="degrees", &
642  fail_if_missing=.true.)
643  call get_param(param_file, mdl, "WESTLON", g%west_lon, &
644  "The western longitude of the domain.", units="degrees", &
645  default=0.0)
646  call get_param(param_file, mdl, "LENLON", g%len_lon, &
647  "The longitudinal length of the domain.", units="degrees", &
648  fail_if_missing=.true.)
649  call get_param(param_file, mdl, "RAD_EARTH", g%Rad_Earth, &
650  "The radius of the Earth.", units="m", default=6.378e6)
651 
652  dlon = g%len_lon/g%Domain%niglobal
653  dlat = g%len_lat/g%Domain%njglobal
654 
655  ! Note that the dynamic grid always uses symmetric memory for the global
656  ! arrays G%gridLatB and G%gridLonB.
657  do j=g%jsg-1,g%jeg
658  latitude = g%south_lat + dlat*(REAL(j-(g%jsg-1)))
659  g%gridLatB(j) = min(max(latitude,-90.),90.)
660  enddo
661  do j=g%jsg,g%jeg
662  latitude = g%south_lat + dlat*(REAL(j-g%jsg)+0.5)
663  g%gridLatT(j) = min(max(latitude,-90.),90.)
664  enddo
665  do i=g%isg-1,g%ieg
666  g%gridLonB(i) = g%west_lon + dlon*(REAL(i-(g%isg-1)))
667  enddo
668  do i=g%isg,g%ieg
669  g%gridLonT(i) = g%west_lon + dlon*(REAL(i-g%isg)+0.5)
670  enddo
671 
672  do j=jsdb,jedb
673  latitude = g%south_lat + dlat* REAL(j+j_offset-(g%jsg-1))
674  grid_latb(j) = min(max(latitude,-90.),90.)
675  enddo
676  do j=jsd,jed
677  latitude = g%south_lat + dlat*(REAL(j+j_offset-g%jsg)+0.5)
678  grid_latt(j) = min(max(latitude,-90.),90.)
679  enddo
680  do i=isdb,iedb
681  grid_lonb(i) = g%west_lon + dlon*REAL(i+i_offset-(g%isg-1))
682  enddo
683  do i=isd,ied
684  grid_lont(i) = g%west_lon + dlon*(REAL(i+i_offset-g%isg)+0.5)
685  enddo
686 
687  dl_di = (g%len_lon * 4.0*atan(1.0)) / (180.0 * g%Domain%niglobal)
688  do j=jsdb,jedb ; do i=isdb,iedb
689  g%geoLonBu(i,j) = grid_lonb(i)
690  g%geoLatBu(i,j) = grid_latb(j)
691 
692 ! The following line is needed to reproduce the solution from
693 ! set_grid_metrics_mercator when used to generate a simple spherical grid.
694  g%dxBu(i,j) = g%Rad_Earth * cos( g%geoLatBu(i,j)*pi_180 ) * dl_di
695 ! G%dxBu(I,J) = G%Rad_Earth * dLon*PI_180 * COS( G%geoLatBu(I,J)*PI_180 )
696  g%dyBu(i,j) = g%Rad_Earth * dlat*pi_180
697  g%areaBu(i,j) = g%dxBu(i,j) * g%dyBu(i,j)
698  enddo; enddo
699 
700  do j=jsdb,jedb ; do i=isd,ied
701  g%geoLonCv(i,j) = grid_lont(i)
702  g%geoLatCv(i,j) = grid_latb(j)
703 
704 ! The following line is needed to reproduce the solution from
705 ! set_grid_metrics_mercator when used to generate a simple spherical grid.
706  g%dxCv(i,j) = g%Rad_Earth * cos( g%geoLatCv(i,j)*pi_180 ) * dl_di
707 ! G%dxCv(i,J) = G%Rad_Earth * (dLon*PI_180) * COS( G%geoLatCv(i,J)*PI_180 )
708  g%dyCv(i,j) = g%Rad_Earth * dlat*pi_180
709  enddo; enddo
710 
711  do j=jsd,jed ; do i=isdb,iedb
712  g%geoLonCu(i,j) = grid_lonb(i)
713  g%geoLatCu(i,j) = grid_latt(j)
714 
715 ! The following line is needed to reproduce the solution from
716 ! set_grid_metrics_mercator when used to generate a simple spherical grid.
717  g%dxCu(i,j) = g%Rad_Earth * cos( g%geoLatCu(i,j)*pi_180 ) * dl_di
718 ! G%dxCu(I,j) = G%Rad_Earth * dLon*PI_180 * COS( latitude )
719  g%dyCu(i,j) = g%Rad_Earth * dlat*pi_180
720  enddo; enddo
721 
722  do j=jsd,jed ; do i=isd,ied
723  g%geoLonT(i,j) = grid_lont(i)
724  g%geoLatT(i,j) = grid_latt(j)
725 
726 ! The following line is needed to reproduce the solution from
727 ! set_grid_metrics_mercator when used to generate a simple spherical grid.
728  g%dxT(i,j) = g%Rad_Earth * cos( g%geoLatT(i,j)*pi_180 ) * dl_di
729 ! G%dxT(i,j) = G%Rad_Earth * dLon*PI_180 * COS( latitude )
730  g%dyT(i,j) = g%Rad_Earth * dlat*pi_180
731 
732 ! latitude = G%geoLatCv(i,J)*PI_180 ! In radians
733 ! dL_di = G%geoLatCv(i,max(jsd,J-1))*PI_180 ! In radians
734 ! G%areaT(i,j) = Rad_Earth**2*dLon*dLat*ABS(SIN(latitude)-SIN(dL_di))
735  g%areaT(i,j) = g%dxT(i,j) * g%dyT(i,j)
736  enddo; enddo
737 
738  call calltree_leave("set_grid_metrics_spherical()")
Here is the call graph for this function:
Here is the caller graph for this function: