SCALE-RM
Functions/Subroutines | Variables
scale_grid Module Reference

module GRID (cartesian) More...

Functions/Subroutines

subroutine, public grid_setup
 Setup. More...
 
subroutine, public grid_allocate
 Allocate arrays. More...
 
subroutine, public grid_generate
 Generate horizontal&vertical grid. More...
 

Variables

real(rp), public dz = 500.0_RP
 length in the main region [m]: z More...
 
real(rp), public dx = 500.0_RP
 length in the main region [m]: x More...
 
real(rp), public dy = 500.0_RP
 length in the main region [m]: y More...
 
real(rp), public buffer_dz = 0.0_RP
 thickness of buffer region [m]: z More...
 
real(rp), public buffer_dx = 0.0_RP
 thickness of buffer region [m]: x More...
 
real(rp), public buffer_dy = 0.0_RP
 thickness of buffer region [m]: y More...
 
real(rp), public bufffact = 1.0_RP
 default strech factor for dx/dy/dz of buffer region More...
 
real(rp), public bufffact_x = -1.0_RP
 strech factor for dx of buffer region More...
 
real(rp), public bufffact_y = -1.0_RP
 strech factor for dy of buffer region More...
 
real(rp), public bufffact_z = -1.0_RP
 strech factor for dz of buffer region More...
 
real(rp), public grid_domain_center_x
 center position of global domain [m]: x More...
 
real(rp), public grid_domain_center_y
 center position of global domain [m]: y More...
 
real(rp), dimension(:), allocatable, public grid_cz
 center coordinate [m]: z, local=global More...
 
real(rp), dimension(:), allocatable, public grid_cx
 center coordinate [m]: x, local More...
 
real(rp), dimension(:), allocatable, public grid_cy
 center coordinate [m]: y, local More...
 
real(rp), dimension(:), allocatable, public grid_cdz
 z-length of control volume [m] More...
 
real(rp), dimension(:), allocatable, public grid_cdx
 x-length of control volume [m] More...
 
real(rp), dimension(:), allocatable, public grid_cdy
 y-length of control volume [m] More...
 
real(rp), dimension(:), allocatable, public grid_rcdz
 reciprocal of center-dz More...
 
real(rp), dimension(:), allocatable, public grid_rcdx
 reciprocal of center-dx More...
 
real(rp), dimension(:), allocatable, public grid_rcdy
 reciprocal of center-dy More...
 
real(rp), dimension(:), allocatable, public grid_fz
 face coordinate [m]: z, local=global More...
 
real(rp), dimension(:), allocatable, public grid_fx
 face coordinate [m]: x, local More...
 
real(rp), dimension(:), allocatable, public grid_fy
 face coordinate [m]: y, local More...
 
real(rp), dimension(:), allocatable, public grid_fdz
 z-length of grid(k+1) to grid(k) [m] More...
 
real(rp), dimension(:), allocatable, public grid_fdx
 x-length of grid(i+1) to grid(i) [m] More...
 
real(rp), dimension(:), allocatable, public grid_fdy
 y-length of grid(j+1) to grid(j) [m] More...
 
real(rp), dimension(:), allocatable, public grid_rfdz
 reciprocal of face-dz More...
 
real(rp), dimension(:), allocatable, public grid_rfdx
 reciprocal of face-dx More...
 
real(rp), dimension(:), allocatable, public grid_rfdy
 reciprocal of face-dy More...
 
real(rp), dimension(:), allocatable, public grid_cbfz
 center buffer factor [0-1]: z More...
 
real(rp), dimension(:), allocatable, public grid_cbfx
 center buffer factor [0-1]: x More...
 
real(rp), dimension(:), allocatable, public grid_cbfy
 center buffer factor [0-1]: y More...
 
real(rp), dimension(:), allocatable, public grid_fbfz
 face buffer factor [0-1]: z More...
 
real(rp), dimension(:), allocatable, public grid_fbfx
 face buffer factor [0-1]: x More...
 
real(rp), dimension(:), allocatable, public grid_fbfy
 face buffer factor [0-1]: y More...
 
real(rp), dimension(:), allocatable, public grid_fxg
 face coordinate [m]: x, global More...
 
real(rp), dimension(:), allocatable, public grid_fyg
 face coordinate [m]: y, global More...
 
real(rp), dimension(:), allocatable, public grid_cxg
 center coordinate [m]: x, global More...
 
real(rp), dimension(:), allocatable, public grid_cyg
 center coordinate [m]: y, global More...
 
real(rp), dimension(:), allocatable, public grid_fbfxg
 face buffer factor [0-1]: x, global More...
 
real(rp), dimension(:), allocatable, public grid_fbfyg
 face buffer factor [0-1]: y, global More...
 
real(rp), dimension(:), allocatable, public grid_cbfxg
 center buffer factor [0-1]: x, global More...
 
real(rp), dimension(:), allocatable, public grid_cbfyg
 center buffer factor [0-1]: y, global More...
 

Detailed Description

module GRID (cartesian)

Description
Grid module for cartesian coordinate
Author
Team SCALE
History
  • 2011-11-11 (H.Yashiro) [new]
  • 2012-03-23 (H.Yashiro) [mod] Explicit index parameter inclusion
  • 2012-06-25 (Y.Sato) [mod] change for unisotropic grid
  • 2012-07-05 (S.Nishizawa) [mod] divided setup into some subroutines

Function/Subroutine Documentation

◆ grid_setup()

subroutine, public scale_grid::grid_setup ( )

Setup.

Definition at line 117 of file scale_grid_cartesian.F90.

References buffer_dx, buffer_dy, buffer_dz, bufffact, bufffact_x, bufffact_y, bufffact_z, dx, dy, dz, grid_allocate(), grid_cx, grid_cy, grid_fx, grid_fy, grid_generate(), scale_grid_index::ia, scale_grid_index::ie, scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_l, scale_stdio::io_lnml, scale_grid_index::is, scale_grid_index::ja, scale_grid_index::je, scale_grid_index::js, and scale_process::prc_mpistop().

Referenced by mod_rm_driver::scalerm(), and mod_rm_prep::scalerm_prep().

117  use scale_process, only: &
119  implicit none
120 
121  namelist / param_grid / &
122  grid_in_basename, &
123  grid_out_basename, &
124  grid_offset_x, &
125  grid_offset_y, &
126  dx, &
127  dy, &
128  dz, &
129  buffer_dz, &
130  buffer_dx, &
131  buffer_dy, &
132  bufffact, &
133  bufffact_x, &
134  bufffact_y, &
135  bufffact_z, &
136  fz, &
137  debug
138 
139  integer :: ierr
140  !---------------------------------------------------------------------------
141 
142  if( io_l ) write(io_fid_log,*)
143  if( io_l ) write(io_fid_log,*) '++++++ Module[GRID] / Categ[ATMOS-RM GRID] / Origin[SCALElib]'
144 
145  call grid_allocate
146 
147  !--- read namelist
148  rewind(io_fid_conf)
149  read(io_fid_conf,nml=param_grid,iostat=ierr)
150  if( ierr < 0 ) then !--- missing
151  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
152  elseif( ierr > 0 ) then !--- fatal error
153  write(*,*) 'xxx Not appropriate names in namelist PARAM_GRID. Check!'
154  call prc_mpistop
155  endif
156  if( io_lnml ) write(io_fid_log,nml=param_grid)
157 
158  if ( bufffact_x < 0.0_rp ) bufffact_x = bufffact
159  if ( bufffact_y < 0.0_rp ) bufffact_y = bufffact
160  if ( bufffact_z < 0.0_rp ) bufffact_z = bufffact
161 
162  if( io_l ) write(io_fid_log,*)
163  if( io_l ) write(io_fid_log,*) '*** Atmosphere grid information ***'
164  if( io_l ) write(io_fid_log,'(1x,A,3(F7.1))') '*** delta Z, X, Y [m] :', dz, dx, dy
165 
166  if ( grid_in_basename /= '' ) then
167  call grid_read
168  else
169  if( io_l ) write(io_fid_log,*) '*** Not found input grid file. Grid position is calculated.'
170 
171  call grid_generate
172  endif
173 
174  if( io_l ) write(io_fid_log,*)
175  if( io_l ) write(io_fid_log,*) '*** Domain size [km] (local) :'
176  if( io_l ) write(io_fid_log,'(1x,6(A,F8.3))') ' X:', &
177  grid_fx(0) *1.e-3_rp, ' -HALO- ', grid_fx(is-1)*1.e-3_rp, ' | ', &
178  grid_cx(is)*1.e-3_rp, ' - ', grid_cx(ie) *1.e-3_rp, ' | ', &
179  grid_fx(ie)*1.e-3_rp, ' -HALO- ', grid_fx(ia) *1.e-3_rp
180  if( io_l ) write(io_fid_log,'(1x,6(A,F8.3))') ' Y:', &
181  grid_fy(0) *1.e-3_rp, ' -HALO- ', grid_fy(js-1)*1.e-3_rp, ' | ', &
182  grid_cy(js)*1.e-3_rp, ' - ', grid_cy(je) *1.e-3_rp, ' | ', &
183  grid_fy(je)*1.e-3_rp, ' -HALO- ', grid_fy(ja) *1.e-3_rp
184 
185  return
integer, public is
start point of inner domain: x, local
integer, public je
end point of inner domain: y, local
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:), allocatable, public grid_fx
face coordinate [m]: x, local
integer, public ia
of x whole cells (local, with HALO)
integer, public js
start point of inner domain: y, local
module PROCESS
real(rp), dimension(:), allocatable, public grid_cx
center coordinate [m]: x, local
integer, public ie
end point of inner domain: x, local
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
real(rp), dimension(:), allocatable, public grid_cy
center coordinate [m]: y, local
integer, public ja
of y whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fy
face coordinate [m]: y, local
Here is the call graph for this function:
Here is the caller graph for this function:

◆ grid_allocate()

subroutine, public scale_grid::grid_allocate ( )

Allocate arrays.

Definition at line 191 of file scale_grid_cartesian.F90.

References grid_cbfx, grid_cbfxg, grid_cbfy, grid_cbfyg, grid_cbfz, grid_cdx, grid_cdy, grid_cdz, grid_cx, grid_cxg, grid_cy, grid_cyg, grid_cz, grid_fbfx, grid_fbfxg, grid_fbfy, grid_fbfyg, grid_fbfz, grid_fdx, grid_fdy, grid_fdz, grid_fx, grid_fxg, grid_fy, grid_fyg, grid_fz, grid_rcdx, grid_rcdy, grid_rcdz, grid_rfdx, grid_rfdy, grid_rfdz, scale_grid_index::ia, scale_grid_index::ihalo, scale_grid_index::imax, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::ja, scale_grid_index::jhalo, scale_grid_index::jmax, scale_grid_index::ka, scale_process::prc_myrank, scale_rm_process::prc_num_x, and scale_rm_process::prc_num_y.

Referenced by grid_setup().

191  use scale_rm_process, only: &
192  prc_num_x, &
193  prc_num_y
194  implicit none
195 
196  integer :: iag, jag
197  !---------------------------------------------------------------------------
198 
199  ! working
200  fz(:) = -1.0_rp
201 
202  ! local domain
203  allocate( grid_cz(ka) )
204  allocate( grid_cx(ia) )
205  allocate( grid_cy(ja) )
206  allocate( grid_cdz(ka) )
207  allocate( grid_cdx(ia) )
208  allocate( grid_cdy(ja) )
209  allocate( grid_rcdz(ka) )
210  allocate( grid_rcdx(ia) )
211  allocate( grid_rcdy(ja) )
212 
213  allocate( grid_fz(0:ka) )
214  allocate( grid_fx(0:ia) )
215  allocate( grid_fy(0:ja) )
216  allocate( grid_fdz(ka-1) )
217  allocate( grid_fdx(ia-1) )
218  allocate( grid_fdy(ja-1) )
219  allocate( grid_rfdz(ka-1) )
220  allocate( grid_rfdx(ia-1) )
221  allocate( grid_rfdy(ja-1) )
222 
223  allocate( grid_cbfz(ka) )
224  allocate( grid_cbfx(ia) )
225  allocate( grid_cbfy(ja) )
226  allocate( grid_fbfz(ka) )
227  allocate( grid_fbfx(ia) )
228  allocate( grid_fbfy(ja) )
229 
230  ! array size (global domain)
231  iag = ihalo + imax*prc_num_x + ihalo
232  jag = jhalo + jmax*prc_num_y + jhalo
233 
234  ! global domain
235  allocate( grid_fxg(0:iag) )
236  allocate( grid_fyg(0:jag) )
237  allocate( grid_cxg( iag) )
238  allocate( grid_cyg( jag) )
239  allocate( grid_cbfxg( iag) )
240  allocate( grid_cbfyg( jag) )
241  allocate( grid_fbfxg( iag) )
242  allocate( grid_fbfyg( jag) )
243 
244  return
integer, public imax
of computational cells: x
integer, public prc_num_x
x length of 2D processor topology
real(rp), dimension(:), allocatable, public grid_cyg
center coordinate [m]: y, global
real(rp), dimension(:), allocatable, public grid_cbfyg
center buffer factor [0-1]: y, global
real(rp), dimension(:), allocatable, public grid_cxg
center coordinate [m]: x, global
real(rp), dimension(:), allocatable, public grid_fdy
y-length of grid(j+1) to grid(j) [m]
real(rp), dimension(:), allocatable, public grid_cz
center coordinate [m]: z, local=global
real(rp), dimension(:), allocatable, public grid_fxg
face coordinate [m]: x, global
real(rp), dimension(:), allocatable, public grid_fbfy
face buffer factor [0-1]: y
real(rp), dimension(:), allocatable, public grid_fx
face coordinate [m]: x, local
integer, public prc_num_y
y length of 2D processor topology
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fbfx
face buffer factor [0-1]: x
real(rp), dimension(:), allocatable, public grid_fdz
z-length of grid(k+1) to grid(k) [m]
integer, public ka
of z whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fbfxg
face buffer factor [0-1]: x, global
real(rp), dimension(:), allocatable, public grid_fz
face coordinate [m]: z, local=global
real(rp), dimension(:), allocatable, public grid_fbfz
face buffer factor [0-1]: z
integer, public jhalo
of halo cells: y
real(rp), dimension(:), allocatable, public grid_cbfx
center buffer factor [0-1]: x
real(rp), dimension(:), allocatable, public grid_fbfyg
face buffer factor [0-1]: y, global
real(rp), dimension(:), allocatable, public grid_cbfz
center buffer factor [0-1]: z
real(rp), dimension(:), allocatable, public grid_cx
center coordinate [m]: x, local
module RM PROCESS
real(rp), dimension(:), allocatable, public grid_cdz
z-length of control volume [m]
real(rp), dimension(:), allocatable, public grid_fdx
x-length of grid(i+1) to grid(i) [m]
real(rp), dimension(:), allocatable, public grid_cdy
y-length of control volume [m]
real(rp), dimension(:), allocatable, public grid_cbfy
center buffer factor [0-1]: y
real(rp), dimension(:), allocatable, public grid_cdx
x-length of control volume [m]
integer, public jmax
of computational cells: y
real(rp), dimension(:), allocatable, public grid_fyg
face coordinate [m]: y, global
real(rp), dimension(:), allocatable, public grid_cy
center coordinate [m]: y, local
real(rp), dimension(:), allocatable, public grid_cbfxg
center buffer factor [0-1]: x, global
integer, public ihalo
of halo cells: x
integer, public ja
of y whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fy
face coordinate [m]: y, local
Here is the caller graph for this function:

◆ grid_generate()

subroutine, public scale_grid::grid_generate ( )

Generate horizontal&vertical grid.

Definition at line 303 of file scale_grid_cartesian.F90.

References buffer_dx, buffer_dy, buffer_dz, bufffact_x, bufffact_y, bufffact_z, dx, dy, dz, grid_cbfx, grid_cbfxg, grid_cbfy, grid_cbfyg, grid_cbfz, grid_cdx, grid_cdy, grid_cdz, grid_cx, grid_cxg, grid_cy, grid_cyg, grid_cz, grid_domain_center_x, grid_domain_center_y, grid_fbfx, grid_fbfxg, grid_fbfy, grid_fbfyg, grid_fbfz, grid_fdx, grid_fdy, grid_fdz, grid_fx, grid_fxg, grid_fy, grid_fyg, grid_fz, grid_rcdx, grid_rcdy, grid_rcdz, grid_rfdx, grid_rfdy, grid_rfdz, scale_grid_index::ia, scale_grid_index::ihalo, scale_grid_index::imax, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::ja, scale_grid_index::jhalo, scale_grid_index::jmax, scale_grid_index::ka, scale_grid_index::ke, scale_grid_index::kmax, scale_grid_index::ks, scale_rm_process::prc_2drank, scale_process::prc_mpistop(), scale_process::prc_myrank, scale_rm_process::prc_num_x, and scale_rm_process::prc_num_y.

Referenced by grid_setup().

303  use scale_process, only: &
304  prc_mpistop, &
305  prc_myrank
306  use scale_rm_process, only: &
307  prc_2drank, &
308  prc_num_x, &
309  prc_num_y
310  implicit none
311 
312  integer :: iag ! # of x whole cells (global, with HALO)
313  integer :: jag ! # of y whole cells (global, with HALO)
314 
315  real(RP), allocatable :: buffz(:), buffx(:), buffy(:)
316  real(RP) :: bufftotz, bufftotx, bufftoty
317 
318  integer :: kbuff, ibuff, jbuff
319  integer :: kmain, imain, jmain
320 
321  integer :: k, i, j, ii, jj
322  !---------------------------------------------------------------------------
323 
324  !##### coordinate in global domain #####
325 
326  ! array size (global domain)
327  iag = ihalo + imax*prc_num_x + ihalo
328  jag = jhalo + jmax*prc_num_y + jhalo
329 
330  allocate( buffx(0:iag) )
331  allocate( buffy(0:jag) )
332 
333  ! X-direction
334  ! calculate buffer grid size
335  buffx(0) = dx
336  bufftotx = 0.0_rp
337 
338  do i = 1, iag
339  if( bufftotx >= buffer_dx ) exit
340 
341  buffx(i) = buffx(i-1) * bufffact_x
342  bufftotx = bufftotx + buffx(i)
343  enddo
344  ibuff = i - 1
345  imain = iag - 2*ibuff - 2*ihalo
346 
347  if ( imain < 0 ) then
348  write(*,*) 'xxx Buffer size (', bufftotx*2.0_rp, ') must be smaller than global domain size (X). Use smaller BUFFER_DX!'
349  call prc_mpistop
350  endif
351 
352  ! horizontal coordinate (global domaim)
353  grid_fxg(ihalo) = grid_offset_x
354  do i = ihalo-1, 0, -1
355  grid_fxg(i) = grid_fxg(i+1) - buffx(ibuff)
356  enddo
357 
358  do i = 1, ihalo
359  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
360  enddo
361 
362  if ( ibuff > 0 ) then
363  do i = ihalo+1, ihalo+ibuff
364  grid_fxg(i) = grid_fxg(i-1) + buffx(ibuff+ihalo+1-i)
365  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
366  enddo
367  endif
368 
369  do i = ihalo+ibuff+1, ihalo+ibuff+imain
370  grid_fxg(i) = grid_fxg(i-1) + dx
371  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
372  enddo
373 
374  if ( ibuff > 0 ) then
375  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
376  grid_fxg(i) = grid_fxg(i-1) + buffx(i-ihalo-ibuff-imain)
377  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
378  enddo
379  endif
380 
381  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
382  grid_fxg(i) = grid_fxg(i-1) + buffx(ibuff)
383  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
384  enddo
385 
386  ! calc buffer factor (global domaim)
387  grid_cbfxg(:) = 0.0_rp
388  grid_fbfxg(:) = 0.0_rp
389  do i = 1, ihalo
390  grid_cbfxg(i) = 1.0_rp
391  grid_fbfxg(i) = 1.0_rp
392  enddo
393 
394  if ( ibuff > 0 ) then
395  do i = ihalo+1, ihalo+ibuff
396  grid_cbfxg(i) = (bufftotx+grid_fxg(ihalo)-grid_cxg(i)) / bufftotx
397  grid_fbfxg(i) = (bufftotx+grid_fxg(ihalo)-grid_fxg(i)) / bufftotx
398  enddo
399 
400  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
401  grid_cbfxg(i) = (bufftotx-grid_fxg(iag-ihalo)+grid_cxg(i)) / bufftotx
402  grid_fbfxg(i) = (bufftotx-grid_fxg(iag-ihalo)+grid_fxg(i)) / bufftotx
403  enddo
404  endif
405 
406  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
407  grid_cbfxg(i) = 1.0_rp
408  grid_fbfxg(i) = 1.0_rp
409  enddo
410 
411  grid_cbfxg(:) = max( min( grid_cbfxg(:), 1.0_rp ), 0.0_rp )
412  grid_fbfxg(:) = max( min( grid_fbfxg(:), 1.0_rp ), 0.0_rp )
413 
414  ! Y-direction
415  ! calculate buffer grid size
416  buffy(0) = dy
417  bufftoty = 0.0_rp
418 
419  do j = 1, jag
420  if( bufftoty >= buffer_dy ) exit
421 
422  buffy(j) = buffy(j-1) * bufffact_y
423  bufftoty = bufftoty + buffy(j)
424  enddo
425  jbuff = j - 1
426  jmain = jag - 2*jbuff - 2*jhalo
427 
428  if ( jmain < 0 ) then
429  write(*,*) 'xxx Buffer size (', bufftoty*2.0_rp, ') must be smaller than global domain size (Y). Use smaller BUFFER_DY!'
430  call prc_mpistop
431  endif
432 
433  ! horizontal coordinate (global domaim)
434  grid_fyg(jhalo) = grid_offset_y
435  do j = jhalo-1, 0, -1
436  grid_fyg(j) = grid_fyg(j+1) - buffy(jbuff)
437  enddo
438 
439  do j = 1, jhalo
440  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
441  enddo
442 
443  if ( jbuff > 0 ) then
444  do j = jhalo+1, jhalo+jbuff
445  grid_fyg(j) = grid_fyg(j-1) + buffy(jbuff+jhalo+1-j)
446  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
447  enddo
448  endif
449 
450  do j = jhalo+jbuff+1, jhalo+jbuff+jmain
451  grid_fyg(j) = grid_fyg(j-1) + dy
452  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
453  enddo
454 
455  if ( jbuff > 0 ) then
456  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
457  grid_fyg(j) = grid_fyg(j-1) + buffy(j-jhalo-jbuff-jmain)
458  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
459  enddo
460  endif
461 
462  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
463  grid_fyg(j) = grid_fyg(j-1) + buffy(jbuff)
464  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
465  enddo
466 
467  ! calc buffer factor (global domaim)
468  grid_cbfyg(:) = 0.0_rp
469  grid_fbfyg(:) = 0.0_rp
470  do j = 1, jhalo
471  grid_cbfyg(j) = 1.0_rp
472  grid_fbfyg(j) = 1.0_rp
473  enddo
474 
475  if ( jbuff > 0 ) then
476  do j = jhalo+1, jhalo+jbuff
477  grid_cbfyg(j) = (bufftoty+grid_fyg(jhalo)-grid_cyg(j)) / bufftoty
478  grid_fbfyg(j) = (bufftoty+grid_fyg(jhalo)-grid_fyg(j)) / bufftoty
479  enddo
480 
481  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
482  grid_cbfyg(j) = (bufftoty-grid_fyg(jag-jhalo)+grid_cyg(j)) / bufftoty
483  grid_fbfyg(j) = (bufftoty-grid_fyg(jag-jhalo)+grid_fyg(j)) / bufftoty
484  enddo
485  endif
486 
487  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
488  grid_cbfyg(j) = 1.0_rp
489  grid_fbfyg(j) = 1.0_rp
490  enddo
491  grid_cbfyg(:) = max( min( grid_cbfyg(:), 1.0_rp ), 0.0_rp )
492  grid_fbfyg(:) = max( min( grid_fbfyg(:), 1.0_rp ), 0.0_rp )
493 
494  deallocate( buffx )
495  deallocate( buffy )
496 
497  !##### coordinate in local domain #####
498 
499  allocate( buffz(0:ka) )
500 
501  if ( minval(fz(1:kmax)) > 0.0_rp ) then ! input from namelist
502  if( io_l ) write(io_fid_log,*) '*** Z coordinate is given from NAMELIST.'
503 
504  if ( kmax < 2 ) then
505  write(*,*) 'xxx If you use FZ, KMAX must be larger than 1. Check!', kmax
506  call prc_mpistop
507  endif
508 
509  ! Z-direction
510  ! calculate buffer grid size
511  bufftotz = 0.0_rp
512 
513  do k = kmax, 2, -1
514  if( bufftotz >= buffer_dz ) exit
515 
516  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
517  enddo
518  kbuff = kmax - k
519  kmain = k
520 
521  if ( kmain < 0 ) then
522  write(*,*) 'xxx Buffer size (', bufftotz, ') must be smaller than domain size (z). Use smaller BUFFER_DZ!'
523  call prc_mpistop
524  endif
525 
526  ! vartical coordinate (local=global domaim)
527  grid_fz(ks-1) = 0.0_rp
528 
529  dz = fz(1)
530  do k = ks-2, 0, -1
531  grid_fz(k) = grid_fz(k+1) - dz
532  enddo
533 
534  do k = ks, ke
535  grid_fz(k) = fz(k-ks+1)
536  enddo
537 
538  dz = fz(kmax) - fz(kmax-1)
539  do k = ke+1, ka
540  grid_fz(k) = grid_fz(k-1) + dz
541  enddo
542 
543  do k = 1, ka
544  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
545  enddo
546 
547  else ! calc using DZ
548 
549  ! Z-direction
550  ! calculate buffer grid size
551  buffz(0) = dz
552  bufftotz = 0.0_rp
553 
554  do k = 1, ka
555  if( bufftotz >= buffer_dz ) exit
556 
557  buffz(k) = buffz(k-1) * bufffact_z
558  bufftotz = bufftotz + buffz(k)
559  enddo
560  kbuff = k - 1
561  kmain = ke - ks + 1 - kbuff
562 
563  if ( kmain < 0 ) then
564  write(*,*) 'xxx Buffer size (', bufftotz, ') must be smaller than domain size (z). Use smaller BUFFER_DZ!'
565  call prc_mpistop
566  endif
567 
568  ! vartical coordinate (local=global domaim)
569  grid_fz(ks-1) = 0.0_rp
570  do k = ks-2, 0, -1
571  grid_fz(k) = grid_fz(k+1) - dz
572  enddo
573 
574  do k = 1, ks-1
575  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
576  enddo
577 
578  do k = ks, ks+kmain-1
579  grid_fz(k) = grid_fz(k-1) + dz
580  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
581  enddo
582 
583  if ( kbuff > 0 ) then
584  do k = ks+kmain, ke
585  grid_fz(k) = grid_fz(k-1) + buffz(k-ks-kmain+1)
586  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
587  enddo
588  endif
589 
590  do k = ke+1, ka
591  grid_fz(k) = grid_fz(k-1) + buffz(kbuff)
592  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
593  enddo
594 
595  endif
596 
597  ! calc buffer factor (global domaim)
598  grid_cbfz(:) = 0.0_rp
599  grid_fbfz(:) = 0.0_rp
600  if ( kbuff > 0 ) then
601  do k = ks+kmain, ke
602  grid_cbfz(k) = (bufftotz-grid_fz(ke)+grid_cz(k)) / bufftotz
603  grid_fbfz(k) = (bufftotz-grid_fz(ke)+grid_fz(k)) / bufftotz
604  enddo
605  endif
606 
607  do k = ke+1, ka
608  grid_cbfz(k) = 1.0_rp
609  grid_fbfz(k) = 1.0_rp
610  enddo
611  grid_cbfz(:) = max( min( grid_cbfz(:), 1.0_rp ), 0.0_rp )
612  grid_fbfz(:) = max( min( grid_fbfz(:), 1.0_rp ), 0.0_rp )
613 
614  deallocate( buffz )
615 
616  ! vartical coordinate (local domaim)
617  do k = 1, ka
618  grid_cdz(k) = grid_fz(k) - grid_fz(k-1)
619  grid_rcdz(k) = 1.0_rp / grid_cdz(k)
620  enddo
621 
622  do k = 1, ka-1
623  grid_fdz(k) = grid_cz(k+1)-grid_cz(k)
624  grid_rfdz(k) = 1.0_rp / grid_fdz(k)
625  enddo
626 
627  ! X-direction
628  ! horizontal coordinate (local domaim)
629  do i = 0, ia
630  ii = i + prc_2drank(prc_myrank,1) * imax
631 
632  grid_fx(i) = grid_fxg(ii)
633  enddo
634 
635  do i = 1, ia
636  ii = i + prc_2drank(prc_myrank,1) * imax
637 
638  grid_cx(i) = grid_cxg(ii)
639  grid_cbfx(i) = grid_cbfxg(ii)
640  grid_fbfx(i) = grid_fbfxg(ii)
641 
642  grid_cdx(i) = grid_fx(i) - grid_fx(i-1)
643  grid_rcdx(i) = 1.0_rp / grid_cdx(i)
644  enddo
645 
646  do i = 1, ia-1
647  grid_fdx(i) = grid_cx(i+1)-grid_cx(i)
648  grid_rfdx(i) = 1.0_rp / grid_fdx(i)
649  enddo
650 
651  ! Y-direction
652  ! horizontal coordinate (local domaim)
653  do j = 0, ja
654  jj = j + prc_2drank(prc_myrank,2) * jmax
655 
656  grid_fy(j) = grid_fyg(jj)
657  enddo
658 
659  do j = 1, ja
660  jj = j + prc_2drank(prc_myrank,2) * jmax
661 
662  grid_cy(j) = grid_cyg(jj)
663  grid_cbfy(j) = grid_cbfyg(jj)
664  grid_fbfy(j) = grid_fbfyg(jj)
665 
666  grid_cdy(j) = grid_fy(j) - grid_fy(j-1)
667  grid_rcdy(j) = 1.0_rp / grid_cdy(j)
668  enddo
669 
670  do j = 1, ja-1
671  grid_fdy(j) = grid_cy(j+1)-grid_cy(j)
672  grid_rfdy(j) = 1.0_rp / grid_fdy(j)
673  enddo
674 
675  grid_domain_center_x = 0.5_rp * ( grid_fxg(0) + grid_fxg(iag) )
676  grid_domain_center_y = 0.5_rp * ( grid_fyg(0) + grid_fyg(jag) )
677 
678  ! report
679  if( io_l ) write(io_fid_log,*)
680  if( io_l ) write(io_fid_log,*) '*** Main/buffer Grid (global) :'
681  if( io_l ) write(io_fid_log,'(1x,2(A,I6))') ' Z: buffer = ', kbuff,' x 1, main = ',kmain
682  if( io_l ) write(io_fid_log,'(1x,2(A,I6))') ' X: buffer = ', ibuff,' x 2, main = ',imain
683  if( io_l ) write(io_fid_log,'(1x,2(A,I6))') ' Y: buffer = ', jbuff,' x 2, main = ',jmain
684  if( io_l ) write(io_fid_log,*)
685  if( io_l ) write(io_fid_log,*) '*** Domain size [km] (global) :'
686  if( io_l ) write(io_fid_log,'(1x,7(A,F8.3))') ' Z:', &
687  grid_fz(0) *1.e-3_rp, ' -HALO- ', &
688  grid_fz(ks-1) *1.e-3_rp, ' | ', &
689  grid_cz(ks) *1.e-3_rp, ' - ', &
690  grid_cz(ke-kbuff)*1.e-3_rp, ' | ', &
691  grid_fz(ke-kbuff)*1.e-3_rp, ' -buffer- ', &
692  grid_fz(ke) *1.e-3_rp, ' -HALO- ', &
693  grid_fz(ka) *1.e-3_rp
694  if( io_l ) write(io_fid_log,'(1x,8(A,F8.3))') ' X:', &
695  grid_fxg(0) *1.e-3_rp, ' -HALO- ', &
696  grid_fxg(ihalo) *1.e-3_rp, ' -buffer- ', &
697  grid_fxg(ihalo+ibuff) *1.e-3_rp, ' | ', &
698  grid_cxg(ihalo+ibuff+1) *1.e-3_rp, ' - ', &
699  grid_cxg(iag-ihalo-ibuff)*1.e-3_rp, ' | ', &
700  grid_fxg(iag-ihalo-ibuff)*1.e-3_rp, ' -buffer- ', &
701  grid_fxg(iag-ihalo) *1.e-3_rp, ' -HALO- ', &
702  grid_fxg(iag) *1.e-3_rp
703  if( io_l ) write(io_fid_log,'(1x,8(A,F8.3))') ' Y:', &
704  grid_fyg(0) *1.e-3_rp, ' -HALO- ', &
705  grid_fyg(jhalo) *1.e-3_rp, ' -buffer- ', &
706  grid_fyg(jhalo+jbuff) *1.e-3_rp, ' | ', &
707  grid_cyg(jhalo+jbuff+1) *1.e-3_rp, ' - ', &
708  grid_cyg(jag-jhalo-jbuff)*1.e-3_rp, ' | ', &
709  grid_fyg(jag-jhalo-jbuff)*1.e-3_rp, ' -buffer- ', &
710  grid_fyg(jag-jhalo) *1.e-3_rp, ' -HALO- ', &
711  grid_fyg(jag) *1.e-3_rp
712  if( io_l ) write(io_fid_log,*)
713  if( io_l ) write(io_fid_log,*) '*** Center Position of Grid (global) :'
714  if( io_l ) write(io_fid_log,'(1x,A,F12.3)') ' X: ', grid_domain_center_x
715  if( io_l ) write(io_fid_log,'(1x,A,F12.3)') ' Y: ', grid_domain_center_y
716 
717  if ( debug ) then
718  if( io_l ) write(io_fid_log,*)
719  if( io_l ) write(io_fid_log,'(1x,A)') &
720  '|============= Vertical Coordinate =============|'
721  if( io_l ) write(io_fid_log,'(1x,A)') &
722  '| k z zh dz buffer k |'
723  if( io_l ) write(io_fid_log,'(1x,A)') &
724  '| [m] [m] [m] factor |'
725 
726  do k = ka, ke+1, -1
727  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
728  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
729  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
730  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
731  enddo
732 
733  k = ke
734  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
735  '| ',grid_fz(k),' ', grid_fbfz(k),k,' | KE = TOA'
736  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
737  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
738 
739  do k = ke-1, ks, -1
740  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
741  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
742  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
743  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
744  enddo
745 
746  k = ks-1
747  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
748  '| ',grid_fz(k),' ', grid_fbfz(k),k,' | KS-1 = surface'
749  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
750  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
751 
752  do k = ks-2, 1, -1
753  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
754  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
755  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
756  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
757  enddo
758 
759  k = 0
760  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
761  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
762 
763  if( io_l ) write(io_fid_log,'(1x,A)') &
764  '|===============================================|'
765 
766 ! if( IO_L ) write(IO_FID_LOG,*)
767 ! if( IO_L ) write(IO_FID_LOG,*) ' ', 0, GRID_FZ(0)
768 ! do k = 1, KA-1
769 ! if( IO_L ) write(IO_FID_LOG,*) k, GRID_CZ(k), GRID_CBFZ(k), GRID_CDZ(k)
770 ! if( IO_L ) write(IO_FID_LOG,*) ' ', k, GRID_FZ(k), GRID_FBFZ(k), GRID_FDZ(k)
771 ! enddo
772 ! k = KA
773 ! if( IO_L ) write(IO_FID_LOG,*) k, GRID_CZ(k), GRID_CBFZ(k), GRID_CDZ(k)
774 ! if( IO_L ) write(IO_FID_LOG,*) ' ', k, GRID_FZ(k), GRID_FBFZ(k)
775 !
776 ! if( IO_L ) write(IO_FID_LOG,*)
777 ! if( IO_L ) write(IO_FID_LOG,*) ' ', 0, GRID_FX(0)
778 ! do i = 1, IA-1
779 ! if( IO_L ) write(IO_FID_LOG,*) i, GRID_CX(i), GRID_CBFX(i), GRID_CDX(i)
780 ! if( IO_L ) write(IO_FID_LOG,*) ' ', i, GRID_FX(i), GRID_FBFX(i), GRID_FDX(i)
781 ! enddo
782 ! i = IA
783 ! if( IO_L ) write(IO_FID_LOG,*) i, GRID_CX(i), GRID_CBFX(i), GRID_CDX(i)
784 ! if( IO_L ) write(IO_FID_LOG,*) ' ', i, GRID_FX(i), GRID_FBFX(i)
785 !
786 ! if( IO_L ) write(IO_FID_LOG,*)
787 ! if( IO_L ) write(IO_FID_LOG,*) ' ', 0, GRID_FY(0)
788 ! do j = 1, JA-1
789 ! if( IO_L ) write(IO_FID_LOG,*) j, GRID_CY(j), GRID_CBFY(j), GRID_CDY(j)
790 ! if( IO_L ) write(IO_FID_LOG,*) ' ', j, GRID_FY(j), GRID_FBFY(j), GRID_FDY(j)
791 ! enddo
792 ! j = JA
793 ! if( IO_L ) write(IO_FID_LOG,*) j, GRID_CY(j), GRID_CBFY(j), GRID_CDY(j)
794 ! if( IO_L ) write(IO_FID_LOG,*) ' ', j, GRID_FY(j), GRID_FBFY(j)
795  endif
796 
797  return
integer, public imax
of computational cells: x
integer, public prc_num_x
x length of 2D processor topology
real(rp), dimension(:), allocatable, public grid_cyg
center coordinate [m]: y, global
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:), allocatable, public grid_cbfyg
center buffer factor [0-1]: y, global
real(rp), dimension(:), allocatable, public grid_cxg
center coordinate [m]: x, global
real(rp), dimension(:), allocatable, public grid_fdy
y-length of grid(j+1) to grid(j) [m]
real(rp), dimension(:), allocatable, public grid_cz
center coordinate [m]: z, local=global
real(rp), dimension(:), allocatable, public grid_fxg
face coordinate [m]: x, global
real(rp), dimension(:), allocatable, public grid_fbfy
face buffer factor [0-1]: y
integer, public ke
end point of inner domain: z, local
real(rp), dimension(:), allocatable, public grid_fx
face coordinate [m]: x, local
integer, public prc_num_y
y length of 2D processor topology
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fbfx
face buffer factor [0-1]: x
real(rp), dimension(:), allocatable, public grid_fdz
z-length of grid(k+1) to grid(k) [m]
integer, public ka
of z whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fbfxg
face buffer factor [0-1]: x, global
integer, public kmax
of computational cells: z
real(rp), dimension(:), allocatable, public grid_fz
face coordinate [m]: z, local=global
real(rp), dimension(:), allocatable, public grid_fbfz
face buffer factor [0-1]: z
integer, public jhalo
of halo cells: y
real(rp), dimension(:), allocatable, public grid_cbfx
center buffer factor [0-1]: x
module PROCESS
real(rp), dimension(:), allocatable, public grid_fbfyg
face buffer factor [0-1]: y, global
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:), allocatable, public grid_cbfz
center buffer factor [0-1]: z
integer, public prc_myrank
process num in local communicator
real(rp), dimension(:), allocatable, public grid_cx
center coordinate [m]: x, local
module RM PROCESS
integer, dimension(:,:), allocatable, public prc_2drank
node index in 2D topology
real(rp), dimension(:), allocatable, public grid_cdz
z-length of control volume [m]
real(rp), dimension(:), allocatable, public grid_fdx
x-length of grid(i+1) to grid(i) [m]
real(rp), dimension(:), allocatable, public grid_cdy
y-length of control volume [m]
real(rp), dimension(:), allocatable, public grid_cbfy
center buffer factor [0-1]: y
real(rp), dimension(:), allocatable, public grid_cdx
x-length of control volume [m]
integer, public jmax
of computational cells: y
real(rp), dimension(:), allocatable, public grid_fyg
face coordinate [m]: y, global
real(rp), dimension(:), allocatable, public grid_cy
center coordinate [m]: y, local
real(rp), dimension(:), allocatable, public grid_cbfxg
center buffer factor [0-1]: x, global
integer, public ihalo
of halo cells: x
integer, public ja
of y whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_fy
face coordinate [m]: y, local
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ dz

real(rp), public scale_grid::dz = 500.0_RP

length in the main region [m]: z

Definition at line 41 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_phy_mp_sn14::atmos_phy_mp_sn14(), grid_generate(), grid_setup(), and scale_grid_real::real_calc_areavol().

41  real(RP), public :: dz = 500.0_rp

◆ dx

real(rp), public scale_grid::dx = 500.0_RP

◆ dy

real(rp), public scale_grid::dy = 500.0_RP

◆ buffer_dz

real(rp), public scale_grid::buffer_dz = 0.0_RP

thickness of buffer region [m]: z

Definition at line 45 of file scale_grid_cartesian.F90.

Referenced by grid_generate(), and grid_setup().

45  real(RP), public :: buffer_dz = 0.0_rp

◆ buffer_dx

real(rp), public scale_grid::buffer_dx = 0.0_RP

thickness of buffer region [m]: x

Definition at line 46 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), grid_generate(), and grid_setup().

46  real(RP), public :: buffer_dx = 0.0_rp

◆ buffer_dy

real(rp), public scale_grid::buffer_dy = 0.0_RP

thickness of buffer region [m]: y

Definition at line 47 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), grid_generate(), and grid_setup().

47  real(RP), public :: buffer_dy = 0.0_rp

◆ bufffact

real(rp), public scale_grid::bufffact = 1.0_RP

default strech factor for dx/dy/dz of buffer region

Definition at line 48 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), and grid_setup().

48  real(RP), public :: bufffact = 1.0_rp

◆ bufffact_x

real(rp), public scale_grid::bufffact_x = -1.0_RP

strech factor for dx of buffer region

Definition at line 49 of file scale_grid_cartesian.F90.

Referenced by grid_generate(), and grid_setup().

49  real(RP), public :: bufffact_x = -1.0_rp

◆ bufffact_y

real(rp), public scale_grid::bufffact_y = -1.0_RP

strech factor for dy of buffer region

Definition at line 50 of file scale_grid_cartesian.F90.

Referenced by grid_generate(), and grid_setup().

50  real(RP), public :: bufffact_y = -1.0_rp

◆ bufffact_z

real(rp), public scale_grid::bufffact_z = -1.0_RP

strech factor for dz of buffer region

Definition at line 51 of file scale_grid_cartesian.F90.

Referenced by grid_generate(), and grid_setup().

51  real(RP), public :: bufffact_z = -1.0_rp

◆ grid_domain_center_x

real(rp), public scale_grid::grid_domain_center_x

center position of global domain [m]: x

Definition at line 53 of file scale_grid_cartesian.F90.

Referenced by grid_generate(), scale_grid_real::real_setup(), and scale_grid_real::real_update_z().

53  real(RP), public :: grid_domain_center_x

◆ grid_domain_center_y

real(rp), public scale_grid::grid_domain_center_y

center position of global domain [m]: y

Definition at line 54 of file scale_grid_cartesian.F90.

Referenced by grid_generate(), scale_grid_real::real_setup(), and scale_grid_real::real_update_z().

54  real(RP), public :: grid_domain_center_y

◆ grid_cz

real(rp), dimension (:), allocatable, public scale_grid::grid_cz

◆ grid_cx

real(rp), dimension (:), allocatable, public scale_grid::grid_cx

◆ grid_cy

real(rp), dimension (:), allocatable, public scale_grid::grid_cy

◆ grid_cdz

real(rp), dimension (:), allocatable, public scale_grid::grid_cdz

◆ grid_cdx

real(rp), dimension (:), allocatable, public scale_grid::grid_cdx

◆ grid_cdy

real(rp), dimension (:), allocatable, public scale_grid::grid_cdy

◆ grid_rcdz

real(rp), dimension(:), allocatable, public scale_grid::grid_rcdz

◆ grid_rcdx

real(rp), dimension(:), allocatable, public scale_grid::grid_rcdx

◆ grid_rcdy

real(rp), dimension(:), allocatable, public scale_grid::grid_rcdy

◆ grid_fz

real(rp), dimension (:), allocatable, public scale_grid::grid_fz

◆ grid_fx

real(rp), dimension (:), allocatable, public scale_grid::grid_fx

face coordinate [m]: x, local

Definition at line 67 of file scale_grid_cartesian.F90.

Referenced by scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), grid_setup(), scale_gridtrans::gtrans_rotcoef(), scale_history::hist_switch(), mod_mkinit::read_sounding(), and scale_grid_real::real_update_z().

67  real(RP), public, allocatable :: grid_fx (:)
real(rp), dimension(:), allocatable, public grid_fx
face coordinate [m]: x, local

◆ grid_fy

real(rp), dimension (:), allocatable, public scale_grid::grid_fy

face coordinate [m]: y, local

Definition at line 68 of file scale_grid_cartesian.F90.

Referenced by scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), grid_setup(), scale_gridtrans::gtrans_rotcoef(), scale_history::hist_switch(), mod_mkinit::read_sounding(), and scale_grid_real::real_update_z().

68  real(RP), public, allocatable :: grid_fy (:)
real(rp), dimension(:), allocatable, public grid_fy
face coordinate [m]: y, local

◆ grid_fdz

real(rp), dimension (:), allocatable, public scale_grid::grid_fdz

◆ grid_fdx

real(rp), dimension (:), allocatable, public scale_grid::grid_fdx

◆ grid_fdy

real(rp), dimension (:), allocatable, public scale_grid::grid_fdy

◆ grid_rfdz

real(rp), dimension(:), allocatable, public scale_grid::grid_rfdz

◆ grid_rfdx

real(rp), dimension(:), allocatable, public scale_grid::grid_rfdx

◆ grid_rfdy

real(rp), dimension(:), allocatable, public scale_grid::grid_rfdy

◆ grid_cbfz

real(rp), dimension(:), allocatable, public scale_grid::grid_cbfz

center buffer factor [0-1]: z

Definition at line 76 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_boundary::atmos_boundary_resume(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_switch(), and scale_land_grid::land_grid_setup().

76  real(RP), public, allocatable :: grid_cbfz(:)
real(rp), dimension(:), allocatable, public grid_cbfz
center buffer factor [0-1]: z

◆ grid_cbfx

real(rp), dimension(:), allocatable, public scale_grid::grid_cbfx

center buffer factor [0-1]: x

Definition at line 77 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_boundary::atmos_boundary_resume(), mod_cnvtopo::cnvtopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_switch(), and scale_land_grid::land_grid_setup().

77  real(RP), public, allocatable :: grid_cbfx(:)
real(rp), dimension(:), allocatable, public grid_cbfx
center buffer factor [0-1]: x

◆ grid_cbfy

real(rp), dimension(:), allocatable, public scale_grid::grid_cbfy

center buffer factor [0-1]: y

Definition at line 78 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_boundary::atmos_boundary_resume(), mod_cnvtopo::cnvtopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_switch(), and scale_land_grid::land_grid_setup().

78  real(RP), public, allocatable :: grid_cbfy(:)
real(rp), dimension(:), allocatable, public grid_cbfy
center buffer factor [0-1]: y

◆ grid_fbfz

real(rp), dimension(:), allocatable, public scale_grid::grid_fbfz

face buffer factor [0-1]: z

Definition at line 79 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_boundary::atmos_boundary_resume(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

79  real(RP), public, allocatable :: grid_fbfz(:)
real(rp), dimension(:), allocatable, public grid_fbfz
face buffer factor [0-1]: z

◆ grid_fbfx

real(rp), dimension(:), allocatable, public scale_grid::grid_fbfx

face buffer factor [0-1]: x

Definition at line 80 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_boundary::atmos_boundary_resume(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

80  real(RP), public, allocatable :: grid_fbfx(:)
real(rp), dimension(:), allocatable, public grid_fbfx
face buffer factor [0-1]: x

◆ grid_fbfy

real(rp), dimension(:), allocatable, public scale_grid::grid_fbfy

face buffer factor [0-1]: y

Definition at line 81 of file scale_grid_cartesian.F90.

Referenced by scale_atmos_boundary::atmos_boundary_resume(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

81  real(RP), public, allocatable :: grid_fbfy(:)
real(rp), dimension(:), allocatable, public grid_fbfy
face buffer factor [0-1]: y

◆ grid_fxg

real(rp), dimension (:), allocatable, public scale_grid::grid_fxg

face coordinate [m]: x, global

Definition at line 83 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

83  real(RP), public, allocatable :: grid_fxg (:)
real(rp), dimension(:), allocatable, public grid_fxg
face coordinate [m]: x, global

◆ grid_fyg

real(rp), dimension (:), allocatable, public scale_grid::grid_fyg

face coordinate [m]: y, global

Definition at line 84 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

84  real(RP), public, allocatable :: grid_fyg (:)
real(rp), dimension(:), allocatable, public grid_fyg
face coordinate [m]: y, global

◆ grid_cxg

real(rp), dimension (:), allocatable, public scale_grid::grid_cxg

center coordinate [m]: x, global

Definition at line 85 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_switch(), and mod_mkinit::interporation_fact().

85  real(RP), public, allocatable :: grid_cxg (:)
real(rp), dimension(:), allocatable, public grid_cxg
center coordinate [m]: x, global

◆ grid_cyg

real(rp), dimension (:), allocatable, public scale_grid::grid_cyg

center coordinate [m]: y, global

Definition at line 86 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

86  real(RP), public, allocatable :: grid_cyg (:)
real(rp), dimension(:), allocatable, public grid_cyg
center coordinate [m]: y, global

◆ grid_fbfxg

real(rp), dimension(:), allocatable, public scale_grid::grid_fbfxg

face buffer factor [0-1]: x, global

Definition at line 87 of file scale_grid_cartesian.F90.

Referenced by scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

87  real(RP), public, allocatable :: grid_fbfxg(:)
real(rp), dimension(:), allocatable, public grid_fbfxg
face buffer factor [0-1]: x, global

◆ grid_fbfyg

real(rp), dimension(:), allocatable, public scale_grid::grid_fbfyg

face buffer factor [0-1]: y, global

Definition at line 88 of file scale_grid_cartesian.F90.

Referenced by scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

88  real(RP), public, allocatable :: grid_fbfyg(:)
real(rp), dimension(:), allocatable, public grid_fbfyg
face buffer factor [0-1]: y, global

◆ grid_cbfxg

real(rp), dimension(:), allocatable, public scale_grid::grid_cbfxg

center buffer factor [0-1]: x, global

Definition at line 89 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

89  real(RP), public, allocatable :: grid_cbfxg(:)
real(rp), dimension(:), allocatable, public grid_cbfxg
center buffer factor [0-1]: x, global

◆ grid_cbfyg

real(rp), dimension(:), allocatable, public scale_grid::grid_cbfyg

center buffer factor [0-1]: y, global

Definition at line 90 of file scale_grid_cartesian.F90.

Referenced by mod_copytopo::copytopo(), scale_fileio::fileio_set_axes(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_switch().

90  real(RP), public, allocatable :: grid_cbfyg(:)
real(rp), dimension(:), allocatable, public grid_cbfyg
center buffer factor [0-1]: y, global