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_fdxg
 center coordinate [m]: x, global More...
 
real(rp), dimension(:), allocatable, public grid_fdyg
 center coordinate [m]: y, global More...
 
real(rp), dimension(:), allocatable, public grid_cdxg
 center coordinate [m]: x, global More...
 
real(rp), dimension(:), allocatable, public grid_cdyg
 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
NAMELIST
  • PARAM_GRID
    nametypedefault valuecomment
    GRID_IN_BASENAME character(len=H_LONG) ''
    GRID_OUT_BASENAME character(len=H_LONG) ''
    GRID_OFFSET_X real(RP) 0.0_RP
    GRID_OFFSET_Y real(RP) 0.0_RP
    DX real(RP) 500.0_RP length in the main region [m]: x
    DY real(RP) 500.0_RP length in the main region [m]: y
    DZ real(RP) 500.0_RP length in the main region [m]: z
    BUFFER_DZ real(RP) 0.0_RP thickness of buffer region [m]: z
    BUFFER_DX real(RP) 0.0_RP thickness of buffer region [m]: x
    BUFFER_DY real(RP) 0.0_RP thickness of buffer region [m]: y
    BUFFER_NZ integer -1 thickness of buffer region by number of grids: z
    BUFFER_NX integer -1 thickness of buffer region by number of grids: x
    BUFFER_NY integer -1 thickness of buffer region by number of grids: y
    BUFFFACT real(RP) 1.0_RP default strech factor for dx/dy/dz of buffer region
    BUFFFACT_X real(RP) -1.0_RP strech factor for dx of buffer region
    BUFFFACT_Y real(RP) -1.0_RP strech factor for dy of buffer region
    BUFFFACT_Z real(RP) -1.0_RP strech factor for dz of buffer region
    FZ real(RP), dimension(KMAX_USER_LIM) user defined center coordinate [m]: z, local=global
    DEBUG logical .false.

History Output
No history output

Function/Subroutine Documentation

◆ grid_setup()

subroutine, public scale_grid::grid_setup ( )

Setup.

Definition at line 125 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_fid_nml, scale_stdio::io_l, scale_stdio::io_nml, 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().

125  use scale_process, only: &
127  implicit none
128 
129  namelist / param_grid / &
130  grid_in_basename, &
131  grid_out_basename, &
132  grid_offset_x, &
133  grid_offset_y, &
134  dx, &
135  dy, &
136  dz, &
137  buffer_dz, &
138  buffer_dx, &
139  buffer_dy, &
140  buffer_nz, &
141  buffer_nx, &
142  buffer_ny, &
143  bufffact, &
144  bufffact_x, &
145  bufffact_y, &
146  bufffact_z, &
147  fz, &
148  debug
149 
150  integer :: ierr
151  !---------------------------------------------------------------------------
152 
153  if( io_l ) write(io_fid_log,*)
154  if( io_l ) write(io_fid_log,*) '++++++ Module[GRID] / Categ[ATMOS-RM GRID] / Origin[SCALElib]'
155 
156  call grid_allocate
157 
158  !--- read namelist
159  rewind(io_fid_conf)
160  read(io_fid_conf,nml=param_grid,iostat=ierr)
161  if( ierr < 0 ) then !--- missing
162  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
163  elseif( ierr > 0 ) then !--- fatal error
164  write(*,*) 'xxx Not appropriate names in namelist PARAM_GRID. Check!'
165  call prc_mpistop
166  endif
167  if( io_nml ) write(io_fid_nml,nml=param_grid)
168 
169  if ( bufffact_x < 0.0_rp ) bufffact_x = bufffact
170  if ( bufffact_y < 0.0_rp ) bufffact_y = bufffact
171  if ( bufffact_z < 0.0_rp ) bufffact_z = bufffact
172 
173  if( io_l ) write(io_fid_log,*)
174  if( io_l ) write(io_fid_log,*) '*** Atmosphere grid information ***'
175  if( io_l ) write(io_fid_log,'(1x,A,3(1x,F9.3))') '*** delta Z, X, Y [m] :', dz, dx, dy
176 
177  if ( grid_in_basename /= '' ) then
178  call grid_read
179  else
180  if( io_l ) write(io_fid_log,*) '*** Not found input grid file. Grid position is calculated.'
181 
182  call grid_generate
183  endif
184 
185  if( io_l ) write(io_fid_log,*)
186  if( io_l ) write(io_fid_log,*) '*** Domain size [km] (local) :'
187  if( io_l ) write(io_fid_log,'(1x,6(A,F9.3))') '*** X:', &
188  grid_fx(0) *1.e-3_rp, ' -HALO- ', grid_fx(is-1)*1.e-3_rp, ' | ', &
189  grid_cx(is)*1.e-3_rp, ' - ', grid_cx(ie) *1.e-3_rp, ' | ', &
190  grid_fx(ie)*1.e-3_rp, ' -HALO- ', grid_fx(ia) *1.e-3_rp
191  if( io_l ) write(io_fid_log,'(1x,6(A,F9.3))') '*** Y:', &
192  grid_fy(0) *1.e-3_rp, ' -HALO- ', grid_fy(js-1)*1.e-3_rp, ' | ', &
193  grid_cy(js)*1.e-3_rp, ' - ', grid_cy(je) *1.e-3_rp, ' | ', &
194  grid_fy(je)*1.e-3_rp, ' -HALO- ', grid_fy(ja) *1.e-3_rp
195 
196  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 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
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 202 of file scale_grid_cartesian.F90.

References grid_cbfx, grid_cbfxg, grid_cbfy, grid_cbfyg, grid_cbfz, grid_cdx, grid_cdxg, grid_cdy, grid_cdyg, 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_fdxg, grid_fdy, grid_fdyg, 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::iag, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::ja, scale_grid_index::jag, 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().

202  use scale_rm_process, only: &
203  prc_num_x, &
204  prc_num_y
205  implicit none
206  !---------------------------------------------------------------------------
207 
208  ! working
209  fz(:) = -1.0_rp
210 
211  ! local domain
212  allocate( grid_cz(ka) )
213  allocate( grid_cx(ia) )
214  allocate( grid_cy(ja) )
215  allocate( grid_cdz(ka) )
216  allocate( grid_cdx(ia) )
217  allocate( grid_cdy(ja) )
218  allocate( grid_rcdz(ka) )
219  allocate( grid_rcdx(ia) )
220  allocate( grid_rcdy(ja) )
221 
222  allocate( grid_fz(0:ka) )
223  allocate( grid_fx(0:ia) )
224  allocate( grid_fy(0:ja) )
225  allocate( grid_fdz(ka-1) )
226  allocate( grid_fdx(ia-1) )
227  allocate( grid_fdy(ja-1) )
228  allocate( grid_rfdz(ka-1) )
229  allocate( grid_rfdx(ia-1) )
230  allocate( grid_rfdy(ja-1) )
231 
232  allocate( grid_cbfz(ka) )
233  allocate( grid_cbfx(ia) )
234  allocate( grid_cbfy(ja) )
235  allocate( grid_fbfz(ka) )
236  allocate( grid_fbfx(ia) )
237  allocate( grid_fbfy(ja) )
238 
239  ! global domain
240  allocate( grid_fxg(0:iag) )
241  allocate( grid_fyg(0:jag) )
242  allocate( grid_cxg( iag) )
243  allocate( grid_cyg( jag) )
244  allocate( grid_fdxg(iag-1) )
245  allocate( grid_fdyg(jag-1) )
246  allocate( grid_cdxg( iag) )
247  allocate( grid_cdyg( jag) )
248  allocate( grid_cbfxg( iag) )
249  allocate( grid_cbfyg( jag) )
250  allocate( grid_fbfxg( iag) )
251  allocate( grid_fbfyg( jag) )
252 
253  return
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_cdyg
center coordinate [m]: y, global
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_cdxg
center coordinate [m]: x, global
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 jag
of computational grids
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]
real(rp), dimension(:), allocatable, public grid_fbfxg
face buffer factor (0-1): x, global
real(rp), dimension(:), allocatable, public grid_fdyg
center coordinate [m]: y, 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 iag
of computational grids
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_fdxg
center coordinate [m]: x, global
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]
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
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 312 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_cdxg, grid_cdy, grid_cdyg, 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_fdxg, grid_fdy, grid_fdyg, 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::iag, scale_grid_index::ihalo, scale_grid_index::imax, scale_grid_index::imaxg, scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::ja, scale_grid_index::jag, scale_grid_index::jhalo, scale_grid_index::jmax, scale_grid_index::jmaxg, 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().

312  use scale_process, only: &
313  prc_mpistop, &
314  prc_myrank
315  use scale_rm_process, only: &
316  prc_2drank, &
317  prc_num_x, &
318  prc_num_y
319  implicit none
320 
321  real(RP), allocatable :: buffz(:), buffx(:), buffy(:)
322  real(RP) :: bufftotz, bufftotx, bufftoty
323 
324  integer :: kbuff, ibuff, jbuff
325  integer :: kmain, imain, jmain
326 
327  logical :: use_user_input
328 
329  integer :: k, i, j, ii, jj
330  !---------------------------------------------------------------------------
331 
332  !##### coordinate in global domain #####
333 
334  allocate( buffx(0:iag) )
335  allocate( buffy(0:jag) )
336 
337  ! X-direction
338  ! calculate buffer grid size
339 
340  if ( buffer_nx > 0 ) then
341  if ( 2*buffer_nx > imaxg ) then
342  write(*,*) 'xxx Buffer grid size (', buffer_nx, &
343  'x2) must be smaller than global domain size (X). Use smaller BUFFER_NX!'
344  call prc_mpistop
345  endif
346 
347  buffx(0) = dx
348  bufftotx = 0.0_rp
349  do i = 1, buffer_nx
350  buffx(i) = buffx(i-1) * bufffact_x
351  bufftotx = bufftotx + buffx(i)
352  enddo
353  ibuff = buffer_nx
354  imain = imaxg - 2*buffer_nx
355 
356  buffer_dx = bufftotx
357  else
358  buffx(0) = dx
359  bufftotx = 0.0_rp
360  do i = 1, iag
361  if( bufftotx >= buffer_dx ) exit
362  buffx(i) = buffx(i-1) * bufffact_x
363  bufftotx = bufftotx + buffx(i)
364  enddo
365  ibuff = i - 1
366  imain = imaxg - 2*ibuff
367 
368  if ( imain < 0 ) then
369  write(*,*) 'xxx Buffer length (', bufftotx, &
370  'x2[m]) must be smaller than global domain size (X). Use smaller BUFFER_DX!'
371  call prc_mpistop
372  endif
373  endif
374 
375  ! horizontal coordinate (global domain)
376  grid_fxg(ihalo) = grid_offset_x
377  do i = ihalo-1, 0, -1
378  grid_fxg(i) = grid_fxg(i+1) - buffx(ibuff)
379  enddo
380 
381  do i = 1, ihalo
382  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
383  enddo
384 
385  if ( ibuff > 0 ) then
386  do i = ihalo+1, ihalo+ibuff
387  grid_fxg(i) = grid_fxg(i-1) + buffx(ibuff+ihalo+1-i)
388  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
389  enddo
390  endif
391 
392  do i = ihalo+ibuff+1, ihalo+ibuff+imain
393  grid_fxg(i) = grid_fxg(i-1) + dx
394  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
395  enddo
396 
397  if ( ibuff > 0 ) then
398  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
399  grid_fxg(i) = grid_fxg(i-1) + buffx(i-ihalo-ibuff-imain)
400  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
401  enddo
402  endif
403 
404  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
405  grid_fxg(i) = grid_fxg(i-1) + buffx(ibuff)
406  grid_cxg(i) = 0.5_rp * ( grid_fxg(i)+grid_fxg(i-1) )
407  enddo
408 
409  do i = 1, iag
410  grid_cdxg(i) = grid_fxg(i) - grid_fxg(i-1)
411  end do
412  do i = 1, iag-1
413  grid_fdxg(i) = grid_cxg(i+1)-grid_cxg(i)
414  end do
415 
416  ! calc buffer factor (global domain)
417  grid_cbfxg(:) = 0.0_rp
418  grid_fbfxg(:) = 0.0_rp
419  do i = 1, ihalo
420  grid_cbfxg(i) = 1.0_rp
421  grid_fbfxg(i) = 1.0_rp
422  enddo
423 
424  if ( ibuff > 0 ) then
425  do i = ihalo+1, ihalo+ibuff
426  grid_cbfxg(i) = (bufftotx+grid_fxg(ihalo)-grid_cxg(i)) / bufftotx
427  grid_fbfxg(i) = (bufftotx+grid_fxg(ihalo)-grid_fxg(i)) / bufftotx
428  enddo
429 
430  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
431  grid_cbfxg(i) = (bufftotx-grid_fxg(iag-ihalo)+grid_cxg(i)) / bufftotx
432  grid_fbfxg(i) = (bufftotx-grid_fxg(iag-ihalo)+grid_fxg(i)) / bufftotx
433  enddo
434  endif
435 
436  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
437  grid_cbfxg(i) = 1.0_rp
438  grid_fbfxg(i) = 1.0_rp
439  enddo
440 
441  grid_cbfxg(:) = max( min( grid_cbfxg(:), 1.0_rp ), 0.0_rp )
442  grid_fbfxg(:) = max( min( grid_fbfxg(:), 1.0_rp ), 0.0_rp )
443 
444  ! Y-direction
445  ! calculate buffer grid size
446 
447  if ( buffer_ny > 0 ) then
448  if ( 2*buffer_ny > jmaxg ) then
449  write(*,*) 'xxx Buffer grid size (', buffer_ny, &
450  'x2) must be smaller than global domain size (Y). Use smaller BUFFER_NY!'
451  call prc_mpistop
452  endif
453 
454  buffy(0) = dy
455  bufftoty = 0.0_rp
456  do j = 1, buffer_ny
457  buffy(j) = buffy(j-1) * bufffact_y
458  bufftoty = bufftoty + buffy(j)
459  enddo
460  jbuff = buffer_ny
461  jmain = jmaxg - 2*buffer_ny
462 
463  buffer_dy = bufftoty
464  else
465  buffy(0) = dy
466  bufftoty = 0.0_rp
467  do j = 1, jag
468  if( bufftoty >= buffer_dy ) exit
469  buffy(j) = buffy(j-1) * bufffact_y
470  bufftoty = bufftoty + buffy(j)
471  enddo
472  jbuff = j - 1
473  jmain = jmaxg - 2*jbuff
474 
475  if ( jmain < 0 ) then
476  write(*,*) 'xxx Buffer length (', bufftoty, &
477  'x2[m]) must be smaller than global domain size (Y). Use smaller BUFFER_DY!'
478  call prc_mpistop
479  endif
480  endif
481 
482  ! horizontal coordinate (global domain)
483  grid_fyg(jhalo) = grid_offset_y
484  do j = jhalo-1, 0, -1
485  grid_fyg(j) = grid_fyg(j+1) - buffy(jbuff)
486  enddo
487 
488  do j = 1, jhalo
489  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
490  enddo
491 
492  if ( jbuff > 0 ) then
493  do j = jhalo+1, jhalo+jbuff
494  grid_fyg(j) = grid_fyg(j-1) + buffy(jbuff+jhalo+1-j)
495  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
496  enddo
497  endif
498 
499  do j = jhalo+jbuff+1, jhalo+jbuff+jmain
500  grid_fyg(j) = grid_fyg(j-1) + dy
501  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
502  enddo
503 
504  if ( jbuff > 0 ) then
505  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
506  grid_fyg(j) = grid_fyg(j-1) + buffy(j-jhalo-jbuff-jmain)
507  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
508  enddo
509  endif
510 
511  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
512  grid_fyg(j) = grid_fyg(j-1) + buffy(jbuff)
513  grid_cyg(j) = 0.5_rp * ( grid_fyg(j)+grid_fyg(j-1) )
514  enddo
515 
516  do j = 1, jag
517  grid_cdyg(j) = grid_fyg(j) - grid_fyg(j-1)
518  end do
519  do j = 1, jag-1
520  grid_fdyg(j) = grid_cyg(j+1)-grid_cyg(j)
521  end do
522 
523  ! calc buffer factor (global domain)
524  grid_cbfyg(:) = 0.0_rp
525  grid_fbfyg(:) = 0.0_rp
526  do j = 1, jhalo
527  grid_cbfyg(j) = 1.0_rp
528  grid_fbfyg(j) = 1.0_rp
529  enddo
530 
531  if ( jbuff > 0 ) then
532  do j = jhalo+1, jhalo+jbuff
533  grid_cbfyg(j) = (bufftoty+grid_fyg(jhalo)-grid_cyg(j)) / bufftoty
534  grid_fbfyg(j) = (bufftoty+grid_fyg(jhalo)-grid_fyg(j)) / bufftoty
535  enddo
536 
537  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
538  grid_cbfyg(j) = (bufftoty-grid_fyg(jag-jhalo)+grid_cyg(j)) / bufftoty
539  grid_fbfyg(j) = (bufftoty-grid_fyg(jag-jhalo)+grid_fyg(j)) / bufftoty
540  enddo
541  endif
542 
543  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
544  grid_cbfyg(j) = 1.0_rp
545  grid_fbfyg(j) = 1.0_rp
546  enddo
547  grid_cbfyg(:) = max( min( grid_cbfyg(:), 1.0_rp ), 0.0_rp )
548  grid_fbfyg(:) = max( min( grid_fbfyg(:), 1.0_rp ), 0.0_rp )
549 
550  deallocate( buffx )
551  deallocate( buffy )
552 
553  !##### coordinate in local domain #####
554 
555  allocate( buffz(0:ka) )
556 
557  use_user_input = .false.
558  if ( maxval(fz(1:kmax_user_lim)) > 0.0_rp ) then ! try to use input from namelist
559  if( io_l ) write(io_fid_log,*) '*** Z coordinate is given from NAMELIST.'
560 
561  if ( kmax < 2 ) then
562  write(*,*) 'xxx KMAX must be larger than 1. Check!', kmax
563  call prc_mpistop
564  endif
565 
566  if ( kmax > kmax_user_lim ) then
567  write(*,*) 'xxx KMAX must be smaller than ', kmax_user_lim, '. Check!', kmax
568  call prc_mpistop
569  endif
570 
571  if ( minval(fz(1:kmax)) <= 0.0_rp ) then
572  write(*,*) 'xxx FZ must be positive. Check! minval(FZ(1:KMAX))=', minval(fz(1:kmax))
573  call prc_mpistop
574  endif
575 
576  use_user_input = .true.
577  endif
578 
579  if ( use_user_input ) then ! input from namelist
580 
581  ! Z-direction
582  ! calculate buffer grid size
583 
584  if ( buffer_nz > 0 ) then
585  if ( buffer_nz > kmax ) then
586  write(*,*) 'xxx Buffer grid size (', buffer_nz, &
587  ') must be smaller than global domain size (Z). Use smaller BUFFER_NZ!'
588  call prc_mpistop
589  endif
590 
591  bufftotz = 0.0_rp
592  do k = kmax, kmax-buffer_nz+1, -1
593  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
594  enddo
595  kbuff = buffer_nz
596  kmain = kmax - buffer_nz
597 
598  buffer_dz = bufftotz
599  else
600  if ( buffer_dz > fz(kmax) ) then
601  write(*,*) 'xxx Buffer length (', buffer_dz, &
602  '[m]) must be smaller than global domain size (Z). Use smaller BUFFER_DZ!'
603  call prc_mpistop
604  endif
605 
606  bufftotz = 0.0_rp
607  do k = kmax, 2, -1
608  if( bufftotz >= buffer_dz ) exit
609  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
610  enddo
611  kbuff = kmax - k
612  kmain = k
613  endif
614 
615  ! vertical coordinate (local=global domain)
616  grid_fz(ks-1) = 0.0_rp
617 
618  dz = fz(1)
619  do k = ks-2, 0, -1
620  grid_fz(k) = grid_fz(k+1) - dz
621  enddo
622 
623  do k = ks, ke
624  grid_fz(k) = fz(k-ks+1)
625  enddo
626 
627  dz = fz(kmax) - fz(kmax-1)
628  do k = ke+1, ka
629  grid_fz(k) = grid_fz(k-1) + dz
630  enddo
631 
632  do k = 1, ka
633  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
634  enddo
635 
636  else ! calc using DZ
637 
638  ! Z-direction
639  ! calculate buffer grid size
640 
641  if ( buffer_nz > 0 ) then
642  if ( buffer_nz > kmax ) then
643  write(*,*) 'xxx Buffer grid size (', buffer_nz, &
644  ') must be smaller than global domain size (Z). Use smaller BUFFER_NZ!'
645  call prc_mpistop
646  endif
647 
648  buffz(0) = dz
649  bufftotz = 0.0_rp
650  do k = 1, buffer_nz
651  buffz(k) = buffz(k-1) * bufffact_z
652  bufftotz = bufftotz + buffz(k)
653  enddo
654  kbuff = buffer_nz
655  kmain = kmax - buffer_nz
656 
657  buffer_dz = bufftotz
658  else
659  buffz(0) = dz
660  bufftotz = 0.0_rp
661  do k = 1, ka
662  if( bufftotz >= buffer_dz ) exit
663  buffz(k) = buffz(k-1) * bufffact_z
664  bufftotz = bufftotz + buffz(k)
665  enddo
666  kbuff = k - 1
667  kmain = kmax - kbuff
668 
669  if ( kmain < 0 ) then
670  write(*,*) 'xxx Buffer length (', bufftotz, &
671  '[m]) must be smaller than global domain size (Z). Use smaller BUFFER_DZ!'
672  call prc_mpistop
673  endif
674  endif
675 
676  ! vertical coordinate (local=global domain)
677  grid_fz(ks-1) = 0.0_rp
678  do k = ks-2, 0, -1
679  grid_fz(k) = grid_fz(k+1) - dz
680  enddo
681 
682  do k = 1, ks-1
683  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
684  enddo
685 
686  do k = ks, ks+kmain-1
687  grid_fz(k) = grid_fz(k-1) + dz
688  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
689  enddo
690 
691  if ( kbuff > 0 ) then
692  do k = ks+kmain, ke
693  grid_fz(k) = grid_fz(k-1) + buffz(k-ks-kmain+1)
694  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
695  enddo
696  endif
697 
698  do k = ke+1, ka
699  grid_fz(k) = grid_fz(k-1) + buffz(kbuff)
700  grid_cz(k) = 0.5_rp * ( grid_fz(k)+grid_fz(k-1) )
701  enddo
702 
703  endif
704 
705  ! calc buffer factor (global domain)
706  grid_cbfz(:) = 0.0_rp
707  grid_fbfz(:) = 0.0_rp
708  if ( kbuff > 0 ) then
709  do k = ks+kmain, ke
710  grid_cbfz(k) = (bufftotz-grid_fz(ke)+grid_cz(k)) / bufftotz
711  grid_fbfz(k) = (bufftotz-grid_fz(ke)+grid_fz(k)) / bufftotz
712  enddo
713  endif
714 
715  do k = ke+1, ka
716  grid_cbfz(k) = 1.0_rp
717  grid_fbfz(k) = 1.0_rp
718  enddo
719  grid_cbfz(:) = max( min( grid_cbfz(:), 1.0_rp ), 0.0_rp )
720  grid_fbfz(:) = max( min( grid_fbfz(:), 1.0_rp ), 0.0_rp )
721 
722  deallocate( buffz )
723 
724  ! vertical coordinate (local domain)
725  do k = 1, ka
726  grid_cdz(k) = grid_fz(k) - grid_fz(k-1)
727  grid_rcdz(k) = 1.0_rp / grid_cdz(k)
728  enddo
729 
730  do k = 1, ka-1
731  grid_fdz(k) = grid_cz(k+1)-grid_cz(k)
732  grid_rfdz(k) = 1.0_rp / grid_fdz(k)
733  enddo
734 
735  ! X-direction
736  ! horizontal coordinate (local domain)
737  do i = 0, ia
738  ii = i + prc_2drank(prc_myrank,1) * imax
739 
740  grid_fx(i) = grid_fxg(ii)
741  enddo
742 
743  do i = 1, ia
744  ii = i + prc_2drank(prc_myrank,1) * imax
745 
746  grid_cx(i) = grid_cxg(ii)
747  grid_cbfx(i) = grid_cbfxg(ii)
748  grid_fbfx(i) = grid_fbfxg(ii)
749 
750  grid_cdx(i) = grid_fx(i) - grid_fx(i-1)
751  grid_rcdx(i) = 1.0_rp / grid_cdx(i)
752  enddo
753 
754  do i = 1, ia-1
755  grid_fdx(i) = grid_cx(i+1)-grid_cx(i)
756  grid_rfdx(i) = 1.0_rp / grid_fdx(i)
757  enddo
758 
759  ! Y-direction
760  ! horizontal coordinate (local domain)
761  do j = 0, ja
762  jj = j + prc_2drank(prc_myrank,2) * jmax
763 
764  grid_fy(j) = grid_fyg(jj)
765  enddo
766 
767  do j = 1, ja
768  jj = j + prc_2drank(prc_myrank,2) * jmax
769 
770  grid_cy(j) = grid_cyg(jj)
771  grid_cbfy(j) = grid_cbfyg(jj)
772  grid_fbfy(j) = grid_fbfyg(jj)
773 
774  grid_cdy(j) = grid_fy(j) - grid_fy(j-1)
775  grid_rcdy(j) = 1.0_rp / grid_cdy(j)
776  enddo
777 
778  do j = 1, ja-1
779  grid_fdy(j) = grid_cy(j+1)-grid_cy(j)
780  grid_rfdy(j) = 1.0_rp / grid_fdy(j)
781  enddo
782 
783  grid_domain_center_x = 0.5_rp * ( grid_fxg(ihalo) + grid_fxg(iag-ihalo) )
784  grid_domain_center_y = 0.5_rp * ( grid_fyg(jhalo) + grid_fyg(jag-jhalo) )
785 
786  ! report
787  if( io_l ) write(io_fid_log,*)
788  if( io_l ) write(io_fid_log,*) '*** Main/buffer Grid (global) :'
789  if( io_l ) write(io_fid_log,'(1x,2(A,I6))') '*** Z: buffer = ', kbuff,' x 1, main = ',kmain
790  if( io_l ) write(io_fid_log,'(1x,2(A,I6))') '*** X: buffer = ', ibuff,' x 2, main = ',imain
791  if( io_l ) write(io_fid_log,'(1x,2(A,I6))') '*** Y: buffer = ', jbuff,' x 2, main = ',jmain
792  if( io_l ) write(io_fid_log,*)
793  if( io_l ) write(io_fid_log,*) '*** Domain size [km] (global) :'
794  if( io_l ) write(io_fid_log,'(1x,7(A,F9.3))') '*** Z:', &
795  grid_fz(0) *1.e-3_rp, ' -HALO- ', &
796  grid_fz(ks-1) *1.e-3_rp, ' | ', &
797  grid_cz(ks) *1.e-3_rp, ' - ', &
798  grid_cz(ke-kbuff)*1.e-3_rp, ' | ', &
799  grid_fz(ke-kbuff)*1.e-3_rp, ' -buffer- ', &
800  grid_fz(ke) *1.e-3_rp, ' -HALO- ', &
801  grid_fz(ka) *1.e-3_rp
802  if( io_l ) write(io_fid_log,'(1x,8(A,F9.3))') '*** X:', &
803  grid_fxg(0) *1.e-3_rp, ' -HALO- ', &
804  grid_fxg(ihalo) *1.e-3_rp, ' -buffer- ', &
805  grid_fxg(ihalo+ibuff) *1.e-3_rp, ' | ', &
806  grid_cxg(ihalo+ibuff+1) *1.e-3_rp, ' - ', &
807  grid_cxg(iag-ihalo-ibuff)*1.e-3_rp, ' | ', &
808  grid_fxg(iag-ihalo-ibuff)*1.e-3_rp, ' -buffer- ', &
809  grid_fxg(iag-ihalo) *1.e-3_rp, ' -HALO- ', &
810  grid_fxg(iag) *1.e-3_rp
811  if( io_l ) write(io_fid_log,'(1x,8(A,F9.3))') '*** Y:', &
812  grid_fyg(0) *1.e-3_rp, ' -HALO- ', &
813  grid_fyg(jhalo) *1.e-3_rp, ' -buffer- ', &
814  grid_fyg(jhalo+jbuff) *1.e-3_rp, ' | ', &
815  grid_cyg(jhalo+jbuff+1) *1.e-3_rp, ' - ', &
816  grid_cyg(jag-jhalo-jbuff)*1.e-3_rp, ' | ', &
817  grid_fyg(jag-jhalo-jbuff)*1.e-3_rp, ' -buffer- ', &
818  grid_fyg(jag-jhalo) *1.e-3_rp, ' -HALO- ', &
819  grid_fyg(jag) *1.e-3_rp
820  if( io_l ) write(io_fid_log,*)
821  if( io_l ) write(io_fid_log,*) '*** Center Position of Grid (global) :'
822  if( io_l ) write(io_fid_log,'(1x,A,F12.3)') '*** X: ', grid_domain_center_x
823  if( io_l ) write(io_fid_log,'(1x,A,F12.3)') '*** Y: ', grid_domain_center_y
824 
825  if( io_l ) write(io_fid_log,*)
826  if( io_l ) write(io_fid_log,'(1x,A)') &
827  '|============= Vertical Coordinate =============|'
828  if( io_l ) write(io_fid_log,'(1x,A)') &
829  '| k z zh dz buffer k |'
830  if( io_l ) write(io_fid_log,'(1x,A)') &
831  '| [m] [m] [m] factor |'
832 
833  do k = ka, ke+1, -1
834  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
835  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
836  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
837  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
838  enddo
839 
840  k = ke
841  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
842  '| ',grid_fz(k),' ', grid_fbfz(k),k,' | KE = TOA'
843  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
844  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
845 
846  do k = ke-1, ks, -1
847  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
848  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
849  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
850  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
851  enddo
852 
853  k = ks-1
854  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
855  '| ',grid_fz(k),' ', grid_fbfz(k),k,' | KS-1 = surface'
856  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
857  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
858 
859  do k = ks-2, 1, -1
860  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,F9.2,I5,A)') &
861  '| ',grid_fz(k),' ', grid_fbfz(k),k,' |'
862  if( io_l ) write(io_fid_log,'(1x,A,I5,F9.2,A,2F9.2,A)') &
863  '|',k,grid_cz(k),' ',grid_cdz(k), grid_cbfz(k),' |'
864  enddo
865 
866  k = 0
867  if( io_l ) write(io_fid_log,'(1x,A,F9.2,A,I5,A)') &
868  '| ',grid_fz(k),' ',k,' |'
869 
870  if( io_l ) write(io_fid_log,'(1x,A)') &
871  '|===============================================|'
872 
873  if ( debug ) then
874  if( io_l ) write(io_fid_log,*)
875  if( io_l ) write(io_fid_log,*) ' ', 0, grid_fx(0)
876  do i = 1, ia-1
877  if( io_l ) write(io_fid_log,*) i, grid_cx(i), grid_cbfx(i), grid_cdx(i)
878  if( io_l ) write(io_fid_log,*) ' ', i, grid_fx(i), grid_fbfx(i), grid_fdx(i)
879  enddo
880  i = ia
881  if( io_l ) write(io_fid_log,*) i, grid_cx(i), grid_cbfx(i), grid_cdx(i)
882  if( io_l ) write(io_fid_log,*) ' ', i, grid_fx(i), grid_fbfx(i)
883 
884  if( io_l ) write(io_fid_log,*)
885  if( io_l ) write(io_fid_log,*) ' ', 0, grid_fy(0)
886  do j = 1, ja-1
887  if( io_l ) write(io_fid_log,*) j, grid_cy(j), grid_cbfy(j), grid_cdy(j)
888  if( io_l ) write(io_fid_log,*) ' ', j, grid_fy(j), grid_fbfy(j), grid_fdy(j)
889  enddo
890  j = ja
891  if( io_l ) write(io_fid_log,*) j, grid_cy(j), grid_cbfy(j), grid_cdy(j)
892  if( io_l ) write(io_fid_log,*) ' ', j, grid_fy(j), grid_fbfy(j)
893  endif
894 
895  return
integer, public imax
of computational cells: x, local
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_cdyg
center coordinate [m]: y, global
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_cdxg
center coordinate [m]: x, global
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 jag
of computational grids
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]
real(rp), dimension(:), allocatable, public grid_fbfxg
face buffer factor (0-1): x, global
real(rp), dimension(:), allocatable, public grid_fdyg
center coordinate [m]: y, 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
integer, public iag
of computational grids
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
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, public imaxg
of computational cells: x, global
real(rp), dimension(:), allocatable, public grid_fdxg
center coordinate [m]: x, global
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
integer, public jmaxg
of computational cells: y, global
real(rp), dimension(:), allocatable, public grid_cdx
x-length of control volume [m]
integer, public jmax
of computational cells: y, local
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
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(), mod_mkinit::interporation_fact(), and scale_grid_real::real_setup().

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(), mod_mkinit::read_sounding(), and scale_grid_real::real_setup().

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

◆ grid_fy

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

◆ 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_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_setup(), and scale_land_grid::land_grid_setup().

76  real(RP), public, allocatable :: GRID_CBFZ(:)

◆ 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(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_setup(), and scale_land_grid::land_grid_setup().

77  real(RP), public, allocatable :: GRID_CBFX(:)

◆ 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(), scale_fileio::fileio_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_setup(), and scale_land_grid::land_grid_setup().

78  real(RP), public, allocatable :: GRID_CBFY(:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_setup().

79  real(RP), public, allocatable :: GRID_FBFZ(:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_setup().

80  real(RP), public, allocatable :: GRID_FBFX(:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_setup().

81  real(RP), public, allocatable :: GRID_FBFY(:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_setup(), and mod_mkinit::mkinit().

83  real(RP), public, allocatable :: GRID_FXG (:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_setup(), mod_mkinit::mkinit(), and mod_mkinit::read_sounding().

84  real(RP), public, allocatable :: GRID_FYG (:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), scale_history::hist_setup(), and mod_mkinit::interporation_fact().

85  real(RP), public, allocatable :: GRID_CXG (:)

◆ 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_write_axes(), grid_allocate(), grid_generate(), and scale_history::hist_setup().

86  real(RP), public, allocatable :: GRID_CYG (:)

◆ grid_fdxg

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

center coordinate [m]: x, global

Definition at line 87 of file scale_grid_cartesian.F90.

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

87  real(RP), public, allocatable :: GRID_FDXG (:)

◆ grid_fdyg

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

center coordinate [m]: y, global

Definition at line 88 of file scale_grid_cartesian.F90.

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

88  real(RP), public, allocatable :: GRID_FDYG (:)

◆ grid_cdxg

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

center coordinate [m]: x, global

Definition at line 89 of file scale_grid_cartesian.F90.

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

89  real(RP), public, allocatable :: GRID_CDXG (:)

◆ grid_cdyg

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

center coordinate [m]: y, global

Definition at line 90 of file scale_grid_cartesian.F90.

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

90  real(RP), public, allocatable :: GRID_CDYG (:)

◆ grid_fbfxg

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

face buffer factor (0-1): x, global

Definition at line 91 of file scale_grid_cartesian.F90.

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

91  real(RP), public, allocatable :: GRID_FBFXG(:)

◆ grid_fbfyg

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

face buffer factor (0-1): y, global

Definition at line 92 of file scale_grid_cartesian.F90.

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

92  real(RP), public, allocatable :: GRID_FBFYG(:)

◆ grid_cbfxg

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

center buffer factor (0-1): x, global

Definition at line 93 of file scale_grid_cartesian.F90.

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

93  real(RP), public, allocatable :: GRID_CBFXG(:)

◆ grid_cbfyg

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

center buffer factor (0-1): y, global

Definition at line 94 of file scale_grid_cartesian.F90.

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

94  real(RP), public, allocatable :: GRID_CBFYG(:)