SCALE-RM
scale_atmos_grid_cartesC.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
11 #include "scalelib.h"
13  !-----------------------------------------------------------------------------
14  !
15  !++ used modules
16  !
17  use scale_precision
18  use scale_io
19  use scale_prof
21  !-----------------------------------------------------------------------------
22  implicit none
23  private
24  !-----------------------------------------------------------------------------
25  !
26  !++ Public procedure
27  !
28  public :: atmos_grid_cartesc_setup
32 
33  !-----------------------------------------------------------------------------
34  !
35  !++ Public parameters & variables
36  !
37  character(len=7), public, parameter :: atmos_grid_cartesc_name = 'cartesC'
38 
39  real(rp), public :: dz, dx, dy
40 
41  real(rp), public, allocatable :: atmos_grid_cartesc_cz (:)
42  real(rp), public, allocatable :: atmos_grid_cartesc_fz (:)
43  real(rp), public, allocatable :: atmos_grid_cartesc_cdz (:)
44  real(rp), public, allocatable :: atmos_grid_cartesc_fdz (:)
45  real(rp), public, allocatable :: atmos_grid_cartesc_rcdz (:)
46  real(rp), public, allocatable :: atmos_grid_cartesc_rfdz (:)
47  real(rp), public, allocatable :: atmos_grid_cartesc_cbfz (:)
48  real(rp), public, allocatable :: atmos_grid_cartesc_fbfz (:)
49 
50  ! land
51  real(rp), public, allocatable :: atmos_grid_cartesc_lcz (:)
52  real(rp), public, allocatable :: atmos_grid_cartesc_lfz (:)
53  real(rp), public, allocatable :: atmos_grid_cartesc_lcdz(:)
54 
55  ! horizontal
56  real(rp), public, allocatable :: atmos_grid_cartesc_cx (:)
57  real(rp), public, allocatable :: atmos_grid_cartesc_cy (:)
58  real(rp), public, allocatable :: atmos_grid_cartesc_fx (:)
59  real(rp), public, allocatable :: atmos_grid_cartesc_fy (:)
60 
61  real(rp), public, allocatable :: atmos_grid_cartesc_cdx (:)
62  real(rp), public, allocatable :: atmos_grid_cartesc_cdy (:)
63  real(rp), public, allocatable :: atmos_grid_cartesc_fdx (:)
64  real(rp), public, allocatable :: atmos_grid_cartesc_fdy (:)
65 
66  real(rp), public, allocatable :: atmos_grid_cartesc_rcdx (:)
67  real(rp), public, allocatable :: atmos_grid_cartesc_rcdy (:)
68  real(rp), public, allocatable :: atmos_grid_cartesc_rfdx (:)
69  real(rp), public, allocatable :: atmos_grid_cartesc_rfdy (:)
70 
71  real(rp), public, allocatable :: atmos_grid_cartesc_cbfx (:)
72  real(rp), public, allocatable :: atmos_grid_cartesc_cbfy (:)
73  real(rp), public, allocatable :: atmos_grid_cartesc_fbfx (:)
74  real(rp), public, allocatable :: atmos_grid_cartesc_fbfy (:)
75 
76  real(rp), public, allocatable :: atmos_grid_cartesc_cxg (:)
77  real(rp), public, allocatable :: atmos_grid_cartesc_cyg (:)
78  real(rp), public, allocatable :: atmos_grid_cartesc_fxg (:)
79  real(rp), public, allocatable :: atmos_grid_cartesc_fyg (:)
80 
81  real(rp), public, allocatable :: atmos_grid_cartesc_cdxg (:)
82  real(rp), public, allocatable :: atmos_grid_cartesc_cdyg (:)
83  real(rp), public, allocatable :: atmos_grid_cartesc_fdxg (:)
84  real(rp), public, allocatable :: atmos_grid_cartesc_fdyg (:)
85 
86  real(rp), public, allocatable :: atmos_grid_cartesc_cbfxg(:)
87  real(rp), public, allocatable :: atmos_grid_cartesc_cbfyg(:)
88  real(rp), public, allocatable :: atmos_grid_cartesc_fbfxg(:)
89  real(rp), public, allocatable :: atmos_grid_cartesc_fbfyg(:)
90 
93 
94  !-----------------------------------------------------------------------------
95  !
96  !++ Private procedure
97  !
98  !-----------------------------------------------------------------------------
99  !
100  !++ Private parameters & variables
101  !
102  !-----------------------------------------------------------------------------
103 contains
104  !-----------------------------------------------------------------------------
106  subroutine atmos_grid_cartesc_setup( &
107  basename, &
108  aggregate )
109  use scale_prc, only: &
110  prc_abort
111  use scale_file, only: &
113  implicit none
114  character(len=*), intent(in), optional :: basename
115  logical, intent(in), optional :: aggregate
116 
117  character(len=H_LONG) :: atmos_grid_cartesc_in_basename = ''
118  logical :: atmos_grid_cartesc_in_aggregate
119 
120  real(rp) :: offset_x = 0.0_rp
121  real(rp) :: offset_y = 0.0_rp
122 
123  real(rp) :: buffer_dz = 0.0_rp
124  real(rp) :: buffer_dx = 0.0_rp
125  real(rp) :: buffer_dy = 0.0_rp
126  real(rp) :: bufffact = 1.0_rp
127  real(rp) :: bufffact_z = -1.0_rp
128  real(rp) :: bufffact_x = -1.0_rp
129  real(rp) :: bufffact_y = -1.0_rp
130 
131  integer :: buffer_nz = -1
132  integer :: buffer_nx = -1
133  integer :: buffer_ny = -1
134 
135  integer, parameter :: fz_max = 300
136  real(rp) :: fz(fz_max)
137 
138  namelist / param_atmos_grid_cartesc / &
139  atmos_grid_cartesc_in_basename, &
140  atmos_grid_cartesc_in_aggregate, &
141  dz, &
142  dx, &
143  dy, &
144  buffer_dz, &
145  buffer_dx, &
146  buffer_dy, &
147  buffer_nz, &
148  buffer_nx, &
149  buffer_ny, &
150  bufffact, &
151  bufffact_z, &
152  bufffact_x, &
153  bufffact_y, &
154  fz, &
155  offset_x, &
156  offset_y
157 
158  integer :: ierr
159  !---------------------------------------------------------------------------
160 
161  log_newline
162  log_info("ATMOS_GRID_CARTESC_setup",*) 'Setup'
163 
164  if ( kmax < 1 ) then
165  log_info("ATMOS_GRID_CARTESC_setup",*) 'Skip because KMAX < 1'
166  return
167  end if
168 
169  fz(:) = -1.0_rp
170 
171  if ( present(basename) ) atmos_grid_cartesc_in_basename = basename
172  if ( present(aggregate) ) then
173  atmos_grid_cartesc_in_aggregate = aggregate
174  else
175  atmos_grid_cartesc_in_aggregate = file_aggregate
176  end if
177 
178  !--- read namelist
179  rewind(io_fid_conf)
180  read(io_fid_conf,nml=param_atmos_grid_cartesc,iostat=ierr)
181  if( ierr < 0 ) then !--- missing
182  log_info("ATMOS_GRID_CARTESC_setup",*) 'Not found namelist. Default used.'
183  elseif( ierr > 0 ) then !--- fatal error
184  log_error("ATMOS_GRID_CARTESC_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_GRID_CARTESC. Check!'
185  call prc_abort
186  endif
187  log_nml(param_atmos_grid_cartesc)
188 
189 
191 
192  if ( atmos_grid_cartesc_in_basename /= '' ) then
193 
194  call atmos_grid_cartesc_read( atmos_grid_cartesc_in_basename, atmos_grid_cartesc_in_aggregate )
195 
196  else
197 
199  dz, dx, dy, fz(:), fz_max, &
200  offset_x, offset_y, &
201  buffer_dz, buffer_dx, buffer_dy, &
202  buffer_nz, buffer_nx, buffer_ny, &
203  bufffact, &
204  bufffact_z, bufffact_x, bufffact_y )
205 
206  end if
207 
209 
210  return
211  end subroutine atmos_grid_cartesc_setup
212 
213  subroutine atmos_grid_cartesc_finalize
214  implicit none
215  !---------------------------------------------------------------------------
216 
217  ! local domain
218  !$acc exit data delete(ATMOS_GRID_CARTESC_CZ, ATMOS_GRID_CARTESC_CX, ATMOS_GRID_CARTESC_CY, ATMOS_GRID_CARTESC_FZ, ATMOS_GRID_CARTESC_FX, ATMOS_GRID_CARTESC_FY)
219  deallocate( atmos_grid_cartesc_cz )
220  deallocate( atmos_grid_cartesc_cx )
221  deallocate( atmos_grid_cartesc_cy )
222  deallocate( atmos_grid_cartesc_fz )
223  deallocate( atmos_grid_cartesc_fx )
224  deallocate( atmos_grid_cartesc_fy )
225 
226  !$acc exit data delete(ATMOS_GRID_CARTESC_CDZ, ATMOS_GRID_CARTESC_CDZ, ATMOS_GRID_CARTESC_CDY, ATMOS_GRID_CARTESC_FDZ, ATMOS_GRID_CARTESC_FDX, ATMOS_GRID_CARTESC_FDY)
227  deallocate( atmos_grid_cartesc_cdz )
228  deallocate( atmos_grid_cartesc_cdx )
229  deallocate( atmos_grid_cartesc_cdy )
230  deallocate( atmos_grid_cartesc_fdz )
231  deallocate( atmos_grid_cartesc_fdx )
232  deallocate( atmos_grid_cartesc_fdy )
233 
234  !$acc exit data delete(ATMOS_GRID_CARTESC_RCDZ, ATMOS_GRID_CARTESC_RCDX, ATMOS_GRID_CARTESC_RCDY, ATMOS_GRID_CARTESC_RFDZ, ATMOS_GRID_CARTESC_RFDX, ATMOS_GRID_CARTESC_RFDY)
235  deallocate( atmos_grid_cartesc_rcdz )
236  deallocate( atmos_grid_cartesc_rcdx )
237  deallocate( atmos_grid_cartesc_rcdy )
238  deallocate( atmos_grid_cartesc_rfdz )
239  deallocate( atmos_grid_cartesc_rfdx )
240  deallocate( atmos_grid_cartesc_rfdy )
241 
242  !$acc exit data delete(ATMOS_GRID_CARTESC_CBFZ, ATMOS_GRID_CARTESC_CBFX, ATMOS_GRID_CARTESC_CBFY, ATMOS_GRID_CARTESC_FBFZ, ATMOS_GRID_CARTESC_FBFX, ATMOS_GRID_CARTESC_FBFY)
243  deallocate( atmos_grid_cartesc_cbfz )
244  deallocate( atmos_grid_cartesc_cbfx )
245  deallocate( atmos_grid_cartesc_cbfy )
246  deallocate( atmos_grid_cartesc_fbfz )
247  deallocate( atmos_grid_cartesc_fbfx )
248  deallocate( atmos_grid_cartesc_fbfy )
249 
250  ! global domain
251  !$acc exit data delete(ATMOS_GRID_CARTESC_CXG, ATMOS_GRID_CARTESC_CYG, ATMOS_GRID_CARTESC_FXG, ATMOS_GRID_CARTESC_FYG)
252  deallocate( atmos_grid_cartesc_cxg )
253  deallocate( atmos_grid_cartesc_cyg )
254  deallocate( atmos_grid_cartesc_fxg )
255  deallocate( atmos_grid_cartesc_fyg )
256 
257  !$acc exit data delete(ATMOS_GRID_CARTESC_CDXG, ATMOS_GRID_CARTESC_CDYG, ATMOS_GRID_CARTESC_FDXG, ATMOS_GRID_CARTESC_FDYG)
258  deallocate( atmos_grid_cartesc_cdxg )
259  deallocate( atmos_grid_cartesc_cdyg )
260  deallocate( atmos_grid_cartesc_fdxg )
261  deallocate( atmos_grid_cartesc_fdyg )
262 
263  !$acc exit data delete(ATMOS_GRID_CARTESC_CBFXG, ATMOS_GRID_CARTESC_CBFYG, ATMOS_GRID_CARTESC_FBFXG, ATMOS_GRID_CARTESC_FBFYG)
264  deallocate( atmos_grid_cartesc_cbfxg )
265  deallocate( atmos_grid_cartesc_cbfyg )
266  deallocate( atmos_grid_cartesc_fbfxg )
267  deallocate( atmos_grid_cartesc_fbfyg )
268 
269  return
270  end subroutine atmos_grid_cartesc_finalize
271 
272  !-----------------------------------------------------------------------------
273  ! private
274  !-----------------------------------------------------------------------------
275 
276  subroutine atmos_grid_cartesc_allocate
277  implicit none
278  !---------------------------------------------------------------------------
279 
280  ! local domain
281  allocate( atmos_grid_cartesc_cz( ka) )
282  allocate( atmos_grid_cartesc_cx( ia) )
283  allocate( atmos_grid_cartesc_cy( ja) )
284  allocate( atmos_grid_cartesc_fz(0:ka) )
285  allocate( atmos_grid_cartesc_fx(0:ia) )
286  allocate( atmos_grid_cartesc_fy(0:ja) )
287  !$acc enter data create(ATMOS_GRID_CARTESC_CZ, ATMOS_GRID_CARTESC_CX, ATMOS_GRID_CARTESC_CY, ATMOS_GRID_CARTESC_FZ, ATMOS_GRID_CARTESC_FX, ATMOS_GRID_CARTESC_FY)
288 
289  allocate( atmos_grid_cartesc_cdz(ka) )
290  allocate( atmos_grid_cartesc_cdx(ia) )
291  allocate( atmos_grid_cartesc_cdy(ja) )
292  allocate( atmos_grid_cartesc_fdz(ka-1) )
293  allocate( atmos_grid_cartesc_fdx(ia-1) )
294  allocate( atmos_grid_cartesc_fdy(ja-1) )
295  !$acc enter data create(ATMOS_GRID_CARTESC_CDZ, ATMOS_GRID_CARTESC_CDX, ATMOS_GRID_CARTESC_CDY, ATMOS_GRID_CARTESC_FDZ, ATMOS_GRID_CARTESC_FDX, ATMOS_GRID_CARTESC_FDY)
296 
297  allocate( atmos_grid_cartesc_rcdz(ka) )
298  allocate( atmos_grid_cartesc_rcdx(ia) )
299  allocate( atmos_grid_cartesc_rcdy(ja) )
300  allocate( atmos_grid_cartesc_rfdz(ka-1) )
301  allocate( atmos_grid_cartesc_rfdx(ia-1) )
302  allocate( atmos_grid_cartesc_rfdy(ja-1) )
303  !$acc enter data create(ATMOS_GRID_CARTESC_RCDZ, ATMOS_GRID_CARTESC_RCDX, ATMOS_GRID_CARTESC_RCDY, ATMOS_GRID_CARTESC_RFDZ, ATMOS_GRID_CARTESC_RFDX, ATMOS_GRID_CARTESC_RFDY)
304 
305  allocate( atmos_grid_cartesc_cbfz( ka) )
306  allocate( atmos_grid_cartesc_cbfx( ia) )
307  allocate( atmos_grid_cartesc_cbfy( ja) )
308  allocate( atmos_grid_cartesc_fbfz(0:ka) )
309  allocate( atmos_grid_cartesc_fbfx(0:ia) )
310  allocate( atmos_grid_cartesc_fbfy(0:ja) )
311  !$acc enter data create(ATMOS_GRID_CARTESC_CBFZ, ATMOS_GRID_CARTESC_CBFX, ATMOS_GRID_CARTESC_CBFY, ATMOS_GRID_CARTESC_FBFZ, ATMOS_GRID_CARTESC_FBFX, ATMOS_GRID_CARTESC_FBFY)
312 
313  ! global domain
314  allocate( atmos_grid_cartesc_cxg( iag) )
315  allocate( atmos_grid_cartesc_cyg( jag) )
316  allocate( atmos_grid_cartesc_fxg(0:iag) )
317  allocate( atmos_grid_cartesc_fyg(0:jag) )
318  !$acc enter data create(ATMOS_GRID_CARTESC_CXG, ATMOS_GRID_CARTESC_CYG, ATMOS_GRID_CARTESC_FXG, ATMOS_GRID_CARTESC_FYG)
319 
320  allocate( atmos_grid_cartesc_cdxg(iag) )
321  allocate( atmos_grid_cartesc_cdyg(jag) )
322  allocate( atmos_grid_cartesc_fdxg(iag-1) )
323  allocate( atmos_grid_cartesc_fdyg(jag-1) )
324  !$acc enter data create(ATMOS_GRID_CARTESC_CDXG, ATMOS_GRID_CARTESC_CDYG, ATMOS_GRID_CARTESC_FDXG, ATMOS_GRID_CARTESC_FDYG)
325 
326  allocate( atmos_grid_cartesc_cbfxg( iag) )
327  allocate( atmos_grid_cartesc_cbfyg( jag) )
328  allocate( atmos_grid_cartesc_fbfxg(0:iag) )
329  allocate( atmos_grid_cartesc_fbfyg(0:jag) )
330  !$acc enter data create(ATMOS_GRID_CARTESC_CBFXG, ATMOS_GRID_CARTESC_CBFYG, ATMOS_GRID_CARTESC_FBFXG, ATMOS_GRID_CARTESC_FBFYG)
331 
332  return
333  end subroutine atmos_grid_cartesc_allocate
334 
335  !-----------------------------------------------------------------------------
337  subroutine atmos_grid_cartesc_read( &
338  basename, aggregate )
339  use scale_file, only: &
340  file_open, &
341  file_read
342  use scale_prc, only: &
343  prc_myrank
344  implicit none
345 
346  character(len=*), intent(in) :: basename
347  logical, intent(in), optional :: aggregate
348 
349  integer :: fid
350 
351  real(rp) :: fdxg(0:iag), fdyg(0:jag)
352  real(rp) :: fdx(0:ia), fdy(0:ja)
353  !---------------------------------------------------------------------------
354 
355 
356  call file_open( basename, fid, rankid=prc_myrank, aggregate=aggregate )
357 
358  call file_read( fid, 'CZ', atmos_grid_cartesc_cz(:) )
359  call file_read( fid, 'CX', atmos_grid_cartesc_cx(:) )
360  call file_read( fid, 'CY', atmos_grid_cartesc_cy(:) )
361  !$acc update device(ATMOS_GRID_CARTESC_CZ, ATMOS_GRID_CARTESC_CX, ATMOS_GRID_CARTESC_CY) async
362 
363  call file_read( fid, 'FZ', atmos_grid_cartesc_fz(:) )
364  call file_read( fid, 'FX', atmos_grid_cartesc_fx(:) )
365  call file_read( fid, 'FY', atmos_grid_cartesc_fy(:) )
366  !$acc update device(ATMOS_GRID_CARTESC_FZ, ATMOS_GRID_CARTESC_FX, ATMOS_GRID_CARTESC_FY) async
367 
368  call file_read( fid, 'CDZ', atmos_grid_cartesc_cdz(:) )
369  call file_read( fid, 'CDX', atmos_grid_cartesc_cdx(:) )
370  call file_read( fid, 'CDY', atmos_grid_cartesc_cdy(:) )
371  !$acc update device(ATMOS_GRID_CARTESC_CDZ, ATMOS_GRID_CARTESC_CDX, ATMOS_GRID_CARTESC_CDY) async
372 
373  call file_read( fid, 'FDZ', atmos_grid_cartesc_fdz(:) )
374  call file_read( fid, 'FDX', fdx(:) )
375  call file_read( fid, 'FDY', fdy(:) )
376  atmos_grid_cartesc_fdx(:) = fdx(1:ia-1)
377  atmos_grid_cartesc_fdy(:) = fdy(1:ja-1)
378  !$acc update device(ATMOS_GRID_CARTESC_FDZ, ATMOS_GRID_CARTESC_FDX, ATMOS_GRID_CARTESC_FDY) async
379 
386  !$acc update device(ATMOS_GRID_CARTESC_RCDZ, ATMOS_GRID_CARTESC_RCDX, ATMOS_GRID_CARTESC_RCDY, ATMOS_GRID_CARTESC_RFDZ, ATMOS_GRID_CARTESC_RFDX, ATMOS_GRID_CARTESC_RFDY) async
387 
388  call file_read( fid, 'CBFZ', atmos_grid_cartesc_cbfz(:) )
389  call file_read( fid, 'CBFX', atmos_grid_cartesc_cbfx(:) )
390  call file_read( fid, 'CBFY', atmos_grid_cartesc_cbfy(:) )
391  call file_read( fid, 'FBFZ', atmos_grid_cartesc_fbfz(:) )
392  call file_read( fid, 'FBFX', atmos_grid_cartesc_fbfx(:) )
393  call file_read( fid, 'FBFY', atmos_grid_cartesc_fbfy(:) )
394  !$acc update device(ATMOS_GRID_CARTESC_CBFZ, ATMOS_GRID_CARTESC_CBFX, ATMOS_GRID_CARTESC_CBFY, ATMOS_GRID_CARTESC_FBFZ, ATMOS_GRID_CARTESC_FBFX, ATMOS_GRID_CARTESC_FBFY) async
395 
396  call file_read( fid, 'CXG', atmos_grid_cartesc_cxg(:) )
397  call file_read( fid, 'CYG', atmos_grid_cartesc_cyg(:) )
398  call file_read( fid, 'FXG', atmos_grid_cartesc_fxg(:) )
399  call file_read( fid, 'FYG', atmos_grid_cartesc_fyg(:) )
400  !$acc update device(ATMOS_GRID_CARTESC_CXG, ATMOS_GRID_CARTESC_CYG, ATMOS_GRID_CARTESC_FXG, ATMOS_GRID_CARTESC_FYG) async
401 
402  call file_read( fid, 'CDXG', atmos_grid_cartesc_cdxg(:) )
403  call file_read( fid, 'CDYG', atmos_grid_cartesc_cdyg(:) )
404  call file_read( fid, 'FDXG', fdxg(:) )
405  call file_read( fid, 'FDYG', fdyg(:) )
406  atmos_grid_cartesc_fdxg(:) = fdxg(1:ia-1)
407  atmos_grid_cartesc_fdyg(:) = fdyg(1:ja-1)
408  !$acc update device(ATMOS_GRID_CARTESC_CDXG, ATMOS_GRID_CARTESC_CDYG, ATMOS_GRID_CARTESC_FDXG, ATMOS_GRID_CARTESC_FDYG) async
409 
412 
413  !$acc wait
414 
415  return
416  end subroutine atmos_grid_cartesc_read
417 
418  !-----------------------------------------------------------------------------
420  subroutine atmos_grid_cartesc_generate( &
421  DZ, DX, DY, FZ, FZ_MAX, &
422  OFFSET_X, OFFSET_Y, &
423  BUFFER_DZ, BUFFER_DX, BUFFER_DY, &
424  BUFFER_NZ, BUFFER_NX, BUFFER_NY, &
425  BUFFFACT, &
426  BUFFFACT_Z, BUFFFACT_X, BUFFFACT_Y )
427  use scale_prc, only: &
428  prc_abort, &
429  prc_myrank
430  use scale_prc_cartesc, only: &
431  prc_2drank, &
432  prc_num_x, &
433  prc_num_y
434  implicit none
435  real(rp), intent(in) :: dz, dx, dy
436  real(rp), intent(in), optional :: fz(:)
437  integer, intent(in), optional :: fz_max
438  real(rp), intent(in), optional :: offset_x, offset_y
439  real(rp), intent(in), optional :: buffer_dz, buffer_dx, buffer_dy
440  integer, intent(in), optional :: buffer_nz, buffer_nx, buffer_ny
441  real(rp), intent(in), optional :: bufffact
442  real(rp), intent(in), optional :: bufffact_z, bufffact_x, bufffact_y
443 
444  real(rp), allocatable :: buffz(:), buffx(:), buffy(:)
445  real(rp) :: bufftotz, bufftotx, bufftoty
446  real(rp) :: fact
447 
448  integer :: kbuff, ibuff, jbuff
449  integer :: kmain, imain, jmain
450 
451  real(rp) :: dz_tmp
452 
453  logical :: use_user_input
454 
455  integer :: k, i, j, ii, jj
456  !---------------------------------------------------------------------------
457 
458  !##### coordinate in global domain #####
459 
460  allocate( buffx(0:iag) )
461  allocate( buffy(0:jag) )
462 
463 
464  ! X-direction
465  ! calculate buffer grid size
466 
467  fact = -1.0_rp
468  if ( present(bufffact_x) ) fact = bufffact_x
469  if ( fact < 0.0_rp .and. present(bufffact) ) fact = bufffact
470  if ( fact < 0.0_rp ) fact = 1.0_rp
471 
472  buffx(0) = dx
473  bufftotx = 0.0_rp
474  ibuff = -1
475  if ( present(buffer_nx) ) ibuff = buffer_nx
476  if ( ibuff > 0 ) then
477  if ( 2*ibuff > imaxg ) then
478  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', ibuff, &
479  'x2) must be smaller than global domain size (X). Use smaller BUFFER_NX!'
480  call prc_abort
481  endif
482 
483  do i = 1, ibuff
484  buffx(i) = buffx(i-1) * fact
485  bufftotx = bufftotx + buffx(i)
486  enddo
487  imain = imaxg - 2*ibuff
488  else if ( present(buffer_dz) ) then
489  do i = 1, iag
490  if( bufftotx >= buffer_dx ) exit
491  buffx(i) = buffx(i-1) * fact
492  bufftotx = bufftotx + buffx(i)
493  enddo
494  ibuff = i - 1
495  imain = imaxg - 2*ibuff
496 
497  if ( imain < 0 ) then
498  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', bufftotx, &
499  'x2[m]) must be smaller than global domain size (X). Use smaller BUFFER_DX!'
500  call prc_abort
501  endif
502  else
503  ibuff = 0
504  imain = imaxg
505  endif
506 
507  ! horizontal coordinate (global domain)
508  if ( present(offset_x) ) then
509  atmos_grid_cartesc_fxg(ihalo) = offset_x
510  else
511  atmos_grid_cartesc_fxg(ihalo) = 0.0_rp
512  end if
513  do i = ihalo-1, 0, -1
514  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i+1) - buffx(ibuff)
515  enddo
516 
517  do i = 1, ihalo
519  enddo
520 
521  if ( ibuff > 0 ) then
522  do i = ihalo+1, ihalo+ibuff
523  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i-1) + buffx(ibuff+ihalo+1-i)
525  enddo
526  endif
527 
528  do i = ihalo+ibuff+1, ihalo+ibuff+imain
531  enddo
532 
533  if ( ibuff > 0 ) then
534  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
535  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i-1) + buffx(i-ihalo-ibuff-imain)
537  enddo
538  endif
539 
540  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
541  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i-1) + buffx(ibuff)
543  enddo
544  !$acc update device(ATMOS_GRID_CARTESC_FXG, ATMOS_GRID_CARTESC_CXG) async
545 
546  do i = 1, iag
548  end do
549  do i = 1, iag-1
551  end do
552  !$acc update device(ATMOS_GRID_CARTESC_CDXG, ATMOS_GRID_CARTESC_FDXG) async
553 
554  ! calc buffer factor (global domain)
555  atmos_grid_cartesc_cbfxg(:) = 0.0_rp
556  atmos_grid_cartesc_fbfxg(:) = 0.0_rp
557  do i = 1, ihalo
558  atmos_grid_cartesc_cbfxg(i) = 1.0_rp
559  enddo
560  do i = 0, ihalo
561  atmos_grid_cartesc_fbfxg(i) = 1.0_rp
562  enddo
563 
564  if ( ibuff > 0 ) then
565  do i = ihalo+1, ihalo+ibuff
568  enddo
569 
570  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
573  enddo
574  endif
575 
576  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
577  atmos_grid_cartesc_cbfxg(i) = 1.0_rp
578  atmos_grid_cartesc_fbfxg(i) = 1.0_rp
579  enddo
580 
581  atmos_grid_cartesc_cbfxg(:) = max( min( atmos_grid_cartesc_cbfxg(:), 1.0_rp ), 0.0_rp )
582  atmos_grid_cartesc_fbfxg(:) = max( min( atmos_grid_cartesc_fbfxg(:), 1.0_rp ), 0.0_rp )
583  !$acc update device(ATMOS_GRID_CARTESC_CBFXG, ATMOS_GRID_CARTESC_FBFXG) async
584 
585  ! Y-direction
586  ! calculate buffer grid size
587 
588  fact = -1.0_rp
589  if ( present(bufffact_y) ) fact = bufffact_y
590  if ( fact < 0.0_rp .and. present(bufffact) )fact = bufffact
591  if ( fact < 0.0_rp ) fact = 1.0_rp
592 
593  buffy(0) = dy
594  bufftoty = 0.0_rp
595  jbuff = -1
596  if ( present(buffer_ny) ) jbuff = buffer_ny
597  if ( jbuff > 0 ) then
598  if ( 2*jbuff > jmaxg ) then
599  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', jbuff, &
600  'x2) must be smaller than global domain size (Y). Use smaller BUFFER_NY!'
601  call prc_abort
602  endif
603 
604  do j = 1, jbuff
605  buffy(j) = buffy(j-1) * fact
606  bufftoty = bufftoty + buffy(j)
607  enddo
608  jmain = jmaxg - 2*jbuff
609  else if ( present(buffer_dy) ) then
610  do j = 1, jag
611  if( bufftoty >= buffer_dy ) exit
612  buffy(j) = buffy(j-1) * fact
613  bufftoty = bufftoty + buffy(j)
614  enddo
615  jbuff = j - 1
616  jmain = jmaxg - 2*jbuff
617 
618  if ( jmain < 0 ) then
619  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', bufftoty, &
620  'x2[m]) must be smaller than global domain size (Y). Use smaller BUFFER_DY!'
621  call prc_abort
622  endif
623  else
624  jbuff = 0
625  jmain = jmaxg
626  endif
627 
628  ! horizontal coordinate (global domain)
629  if ( present(offset_y) ) then
630  atmos_grid_cartesc_fyg(jhalo) = offset_y
631  else
632  atmos_grid_cartesc_fyg(jhalo) = 0.0_rp
633  end if
634  do j = jhalo-1, 0, -1
635  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j+1) - buffy(jbuff)
636  enddo
637 
638  do j = 1, jhalo
640  enddo
641 
642  if ( jbuff > 0 ) then
643  do j = jhalo+1, jhalo+jbuff
644  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j-1) + buffy(jbuff+jhalo+1-j)
646  enddo
647  endif
648 
649  do j = jhalo+jbuff+1, jhalo+jbuff+jmain
652  enddo
653 
654  if ( jbuff > 0 ) then
655  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
656  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j-1) + buffy(j-jhalo-jbuff-jmain)
658  enddo
659  endif
660 
661  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
662  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j-1) + buffy(jbuff)
664  enddo
665  !$acc update device(ATMOS_GRID_CARTESC_FYG, ATMOS_GRID_CARTESC_CYG) async
666 
667  do j = 1, jag
669  end do
670  do j = 1, jag-1
672  end do
673  !$acc update device(ATMOS_GRID_CARTESC_CDYG, ATMOS_GRID_CARTESC_FDYG) async
674 
675  ! calc buffer factor (global domain)
676  atmos_grid_cartesc_cbfyg(:) = 0.0_rp
677  atmos_grid_cartesc_fbfyg(:) = 0.0_rp
678  do j = 1, jhalo
679  atmos_grid_cartesc_cbfyg(j) = 1.0_rp
680  enddo
681  do j = 0, jhalo
682  atmos_grid_cartesc_fbfyg(j) = 1.0_rp
683  enddo
684 
685  if ( jbuff > 0 ) then
686  do j = jhalo+1, jhalo+jbuff
689  enddo
690 
691  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
694  enddo
695  endif
696 
697  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
698  atmos_grid_cartesc_cbfyg(j) = 1.0_rp
699  atmos_grid_cartesc_fbfyg(j) = 1.0_rp
700  enddo
701  atmos_grid_cartesc_cbfyg(:) = max( min( atmos_grid_cartesc_cbfyg(:), 1.0_rp ), 0.0_rp )
702  atmos_grid_cartesc_fbfyg(:) = max( min( atmos_grid_cartesc_fbfyg(:), 1.0_rp ), 0.0_rp )
703  !$acc update device(ATMOS_GRID_CARTESC_CBFYG, ATMOS_GRID_CARTESC_FBFYG) async
704 
705  deallocate( buffx )
706  deallocate( buffy )
707 
708  !##### coordinate in local domain #####
709 
710  allocate( buffz(0:ka) )
711 
712  use_user_input = .false.
713  if ( present(fz) ) then
714  if ( maxval(fz(:)) > 0.0_rp ) then ! try to use input from namelist
715  log_info("ATMOS_GRID_CARTESC_generate",*) 'Z coordinate is given from NAMELIST.'
716 
717  if ( kmax < 2 ) then
718  log_error("ATMOS_GRID_CARTESC_generate",*) 'KMAX must be larger than 1. Check!', kmax
719  call prc_abort
720  endif
721 
722  if ( kmax > fz_max ) then
723  log_error("ATMOS_GRID_CARTESC_generate",*) 'KMAX must be smaller than ', fz_max, '. Check!', kmax
724  call prc_abort
725  endif
726 
727  if ( minval(fz(1:kmax)) <= 0.0_rp ) then
728  log_error("ATMOS_GRID_CARTESC_generate",*) 'FZ must be positive. Check! minval(FZ(1:KMAX))=', minval(fz(1:kmax))
729  call prc_abort
730  endif
731 
732  use_user_input = .true.
733  endif
734  end if
735 
736  if ( use_user_input ) then ! input from namelist
737 
738  ! Z-direction
739  ! calculate buffer grid size
740 
741  kbuff = -1
742  if ( present(buffer_nz) ) kbuff = buffer_nz
743  if ( kbuff > 0 ) then
744  if ( kbuff > kmax ) then
745  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', kbuff, &
746  ') must be smaller than global domain size (Z). Use smaller BUFFER_NZ!'
747  call prc_abort
748  endif
749 
750  bufftotz = 0.0_rp
751  do k = kmax, kmax-kbuff+1, -1
752  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
753  enddo
754  kmain = kmax - kbuff
755  else if ( present(buffer_dz) ) then
756  if ( buffer_dz > fz(kmax) ) then
757  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', buffer_dz, &
758  '[m]) must be smaller than global domain size (Z). Use smaller BUFFER_DZ!'
759  call prc_abort
760  endif
761 
762  bufftotz = 0.0_rp
763  do k = kmax, 2, -1
764  if( bufftotz >= buffer_dz ) exit
765  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
766  enddo
767  kbuff = kmax - k
768  kmain = k
769  else
770  bufftotz = 0.0_rp
771  kbuff = 0
772  kmain = kmax
773  endif
774 
775  ! vertical coordinate (local=global domain)
776  atmos_grid_cartesc_fz(ks-1) = 0.0_rp
777 
778  dz_tmp = fz(1)
779  do k = ks-2, 0, -1
781  enddo
782 
783  do k = ks, ke
784  atmos_grid_cartesc_fz(k) = fz(k-ks+1)
785  enddo
786 
787  dz_tmp = fz(kmax) - fz(kmax-1)
788  do k = ke+1, ka
790  enddo
791 
792  do k = 1, ka
794  enddo
795 
796  else ! calc using DZ
797 
798  ! Z-direction
799  ! calculate buffer grid size
800 
801  fact = -1.0_rp
802  if ( present(bufffact_z) ) fact = bufffact_z
803  if ( fact < 0.0_rp .and. present(bufffact) ) fact = bufffact
804  if ( fact < 0.0_rp ) fact = 1.0_rp
805 
806  buffz(0) = dz
807  bufftotz = 0.0_rp
808  kbuff = -1
809  if ( present(buffer_nz) ) kbuff = buffer_nz
810  if ( kbuff > 0 ) then
811  if ( kbuff > kmax ) then
812  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', kbuff, &
813  ') must be smaller than global domain size (Z). Use smaller BUFFER_NZ!'
814  call prc_abort
815  endif
816 
817  do k = 1, kbuff
818  buffz(k) = buffz(k-1) * fact
819  bufftotz = bufftotz + buffz(k)
820  enddo
821  kmain = kmax - kbuff
822  else if ( present(buffer_dz) ) then
823  do k = 1, ka
824  if( bufftotz >= buffer_dz ) exit
825  buffz(k) = buffz(k-1) * fact
826  bufftotz = bufftotz + buffz(k)
827  enddo
828  kbuff = k - 1
829  kmain = kmax - kbuff
830 
831  if ( kmain < 0 ) then
832  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', bufftotz, &
833  '[m]) must be smaller than global domain size (Z). Use smaller BUFFER_DZ!'
834  call prc_abort
835  endif
836  else
837  kbuff = 0
838  kmain = kmax
839  endif
840 
841  ! vertical coordinate (local=global domain)
842  atmos_grid_cartesc_fz(ks-1) = 0.0_rp
843  do k = ks-2, 0, -1
845  enddo
846 
847  do k = 1, ks-1
849  enddo
850 
851  do k = ks, ks+kmain-1
854  enddo
855 
856  if ( kbuff > 0 ) then
857  do k = ks+kmain, ke
858  atmos_grid_cartesc_fz(k) = atmos_grid_cartesc_fz(k-1) + buffz(k-ks-kmain+1)
860  enddo
861  endif
862 
863  do k = ke+1, ka
864  atmos_grid_cartesc_fz(k) = atmos_grid_cartesc_fz(k-1) + buffz(kbuff)
866  enddo
867 
868  endif
869  !$acc update device(ATMOS_GRID_CARTESC_FZ, ATMOS_GRID_CARTESC_CZ) async
870 
871  ! calc buffer factor (global domain)
872  atmos_grid_cartesc_cbfz(:) = 0.0_rp
873  atmos_grid_cartesc_fbfz(:) = 0.0_rp
874  if ( kbuff > 0 ) then
875  do k = ks+kmain, ke
878  enddo
879  endif
880 
881  do k = ke+1, ka
882  atmos_grid_cartesc_cbfz(k) = 1.0_rp
883  atmos_grid_cartesc_fbfz(k) = 1.0_rp
884  enddo
885  atmos_grid_cartesc_cbfz(:) = max( min( atmos_grid_cartesc_cbfz(:), 1.0_rp ), 0.0_rp )
886  atmos_grid_cartesc_fbfz(:) = max( min( atmos_grid_cartesc_fbfz(:), 1.0_rp ), 0.0_rp )
887  !$acc update device(ATMOS_GRID_CARTESC_CBFZ, ATMOS_GRID_CARTESC_FBFZ) async
888 
889  deallocate( buffz )
890 
891  ! vertical coordinate (local domain)
892  do k = 1, ka
895  enddo
896 
897  do k = 1, ka-1
900  enddo
901  !$acc update device(ATMOS_GRID_CARTESC_CDZ, ATMOS_GRID_CARTESC_FDZ, ATMOS_GRID_CARTESC_RCDZ, ATMOS_GRID_CARTESC_RFDZ) async
902 
903  ! X-direction
904  ! horizontal coordinate (local domain)
905  do i = 0, ia
906  ii = i + prc_2drank(prc_myrank,1) * imax
907 
909  enddo
910 
911  ii = prc_2drank(prc_myrank,1) * imax
913  do i = 1, ia
914  ii = i + prc_2drank(prc_myrank,1) * imax
915 
919 
922  enddo
923 
924  do i = 1, ia-1
927  enddo
928  !$acc update device(ATMOS_GRID_CARTESC_CX, ATMOS_GRID_CARTESC_FX, ATMOS_GRID_CARTESC_CDX, ATMOS_GRID_CARTESC_FDX, ATMOS_GRID_CARTESC_RCDX, ATMOS_GRID_CARTESC_RFDX, ATMOS_GRID_CARTESC_CBFX, ATMOS_GRID_CARTESC_FBFX) async
929 
930  ! Y-direction
931  ! horizontal coordinate (local domain)
932  do j = 0, ja
933  jj = j + prc_2drank(prc_myrank,2) * jmax
934 
936  enddo
937 
938  jj = prc_2drank(prc_myrank,2) * jmax
940  do j = 1, ja
941  jj = j + prc_2drank(prc_myrank,2) * jmax
942 
946 
949  enddo
950 
951  do j = 1, ja-1
954  enddo
955  !$acc update device(ATMOS_GRID_CARTESC_CY, ATMOS_GRID_CARTESC_FY, ATMOS_GRID_CARTESC_CDY, ATMOS_GRID_CARTESC_FDY, ATMOS_GRID_CARTESC_RCDY, ATMOS_GRID_CARTESC_RFDY, ATMOS_GRID_CARTESC_CBFY, ATMOS_GRID_CARTESC_FBFY) async
956 
959 
960  ! report
961  log_newline
962  log_info("ATMOS_GRID_CARTESC_generate",*) 'Grid information '
963  log_info_cont('(1x,A,3(1x,F9.3))') 'delta Z, X, Y [m] :', dz, dx, dy
964 
965  log_newline
966  log_info("ATMOS_GRID_CARTESC_generate",*) 'Main/buffer Grid (global) :'
967  log_info_cont('(1x,2(A,I6))') 'Z: buffer = ', kbuff,' x 1, main = ',kmain
968  log_info_cont('(1x,2(A,I6))') 'X: buffer = ', ibuff,' x 2, main = ',imain
969  log_info_cont('(1x,2(A,I6))') 'Y: buffer = ', jbuff,' x 2, main = ',jmain
970 
971  log_newline
972  log_info("ATMOS_GRID_CARTESC_generate",*) 'Domain size [km] (global) :'
973  log_info_cont('(1x,7(A,F9.3))') 'Z:', &
974  atmos_grid_cartesc_fz(0) *1.e-3_rp, ' -HALO- ', &
975  atmos_grid_cartesc_fz(ks-1) *1.e-3_rp, ' | ', &
976  atmos_grid_cartesc_cz(ks) *1.e-3_rp, ' - ', &
977  atmos_grid_cartesc_cz(ke-kbuff)*1.e-3_rp, ' | ', &
978  atmos_grid_cartesc_fz(ke-kbuff)*1.e-3_rp, ' -buffer- ', &
979  atmos_grid_cartesc_fz(ke) *1.e-3_rp, ' -HALO- ', &
980  atmos_grid_cartesc_fz(ka) *1.e-3_rp
981  log_info_cont('(1x,8(A,F9.3))') 'X:', &
982  atmos_grid_cartesc_fxg(0) *1.e-3_rp, ' -HALO- ', &
983  atmos_grid_cartesc_fxg(ihalo) *1.e-3_rp, ' -buffer- ', &
984  atmos_grid_cartesc_fxg(ihalo+ibuff) *1.e-3_rp, ' | ', &
985  atmos_grid_cartesc_cxg(ihalo+ibuff+1) *1.e-3_rp, ' - ', &
986  atmos_grid_cartesc_cxg(iag-ihalo-ibuff)*1.e-3_rp, ' | ', &
987  atmos_grid_cartesc_fxg(iag-ihalo-ibuff)*1.e-3_rp, ' -buffer- ', &
988  atmos_grid_cartesc_fxg(iag-ihalo) *1.e-3_rp, ' -HALO- ', &
989  atmos_grid_cartesc_fxg(iag) *1.e-3_rp
990  log_info_cont('(1x,8(A,F9.3))') 'Y:', &
991  atmos_grid_cartesc_fyg(0) *1.e-3_rp, ' -HALO- ', &
992  atmos_grid_cartesc_fyg(jhalo) *1.e-3_rp, ' -buffer- ', &
993  atmos_grid_cartesc_fyg(jhalo+jbuff) *1.e-3_rp, ' | ', &
994  atmos_grid_cartesc_cyg(jhalo+jbuff+1) *1.e-3_rp, ' - ', &
995  atmos_grid_cartesc_cyg(jag-jhalo-jbuff)*1.e-3_rp, ' | ', &
996  atmos_grid_cartesc_fyg(jag-jhalo-jbuff)*1.e-3_rp, ' -buffer- ', &
997  atmos_grid_cartesc_fyg(jag-jhalo) *1.e-3_rp, ' -HALO- ', &
998  atmos_grid_cartesc_fyg(jag) *1.e-3_rp
999 
1000  !$acc wait
1001 
1002  return
1003  end subroutine atmos_grid_cartesc_generate
1004 
1005  !-----------------------------------------------------------------------------
1008  integer :: k
1009 
1010  log_newline
1011  log_info("ATMOS_GRID_CARTESC_output_info",*) 'Center Position of Grid (global) :'
1012  log_info_cont('(1x,A,F12.3)') 'X: ', atmos_grid_cartesc_domain_center_x
1013  log_info_cont('(1x,A,F12.3)') 'Y: ', atmos_grid_cartesc_domain_center_y
1014 
1015 
1016  log_newline
1017  log_info("ATMOS_GRID_CARTESC_output_info",*) 'Domain size [km] (local) :'
1018  log_info_cont('(1x,6(A,F9.3))') 'X:', &
1019  atmos_grid_cartesc_fx(0) *1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fx(is-1)*1.e-3_rp, ' | ', &
1020  atmos_grid_cartesc_cx(is)*1.e-3_rp, ' - ', atmos_grid_cartesc_cx(ie) *1.e-3_rp, ' | ', &
1021  atmos_grid_cartesc_fx(ie)*1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fx(ia) *1.e-3_rp
1022  log_info_cont('(1x,6(A,F9.3))') 'Y:', &
1023  atmos_grid_cartesc_fy(0) *1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fy(js-1)*1.e-3_rp, ' | ', &
1024  atmos_grid_cartesc_cy(js)*1.e-3_rp, ' - ', atmos_grid_cartesc_cy(je) *1.e-3_rp, ' | ', &
1025  atmos_grid_cartesc_fy(je)*1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fy(ja) *1.e-3_rp
1026 
1027 
1028  log_newline
1029  log_info("ATMOS_GRID_CARTESC_output_info",'(1x,A)') 'Vertical Coordinate'
1030  log_info_cont('(1x,A)') '|===============================================|'
1031  log_info_cont('(1x,A)') '| k z zh dz buffer k |'
1032  log_info_cont('(1x,A)') '| [m] [m] [m] factor |'
1033 
1034  do k = ka, ke+1, -1
1035  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
1036  log_info_cont('(1x,A,I5,F9.2,A,2F9.2,A)') '|',k,atmos_grid_cartesc_cz(k),' ',atmos_grid_cartesc_cdz(k), atmos_grid_cartesc_cbfz(k),' |'
1037  enddo
1038 
1039  k = ke
1040  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' | KE = TOA'
1041  log_info_cont('(1x,A,I5,F9.2,A,2F9.2,A)') '|',k,atmos_grid_cartesc_cz(k),' ',atmos_grid_cartesc_cdz(k), atmos_grid_cartesc_cbfz(k),' |'
1042 
1043  do k = ke-1, ks, -1
1044  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
1045  log_info_cont('(1x,A,I5,F9.2,A,2F9.2,A)') '|',k,atmos_grid_cartesc_cz(k),' ',atmos_grid_cartesc_cdz(k), atmos_grid_cartesc_cbfz(k),' |'
1046  enddo
1047 
1048  k = ks-1
1049  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' | KS-1 = surface'
1050  log_info_cont('(1x,A,I5,F9.2,A,2F9.2,A)') '|',k,atmos_grid_cartesc_cz(k),' ',atmos_grid_cartesc_cdz(k), atmos_grid_cartesc_cbfz(k),' |'
1051 
1052  do k = ks-2, 1, -1
1053  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
1054  log_info_cont('(1x,A,I5,F9.2,A,2F9.2,A)') '|',k,atmos_grid_cartesc_cz(k),' ',atmos_grid_cartesc_cdz(k), atmos_grid_cartesc_cbfz(k),' |'
1055  enddo
1056 
1057  k = 0
1058  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
1059 
1060  log_info_cont('(1x,A)') '|===============================================|'
1061 
1062 
1063  return
1064  end subroutine atmos_grid_cartesc_output_info
1065 
1066 end module scale_atmos_grid_cartesc
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:43
scale_atmos_grid_cartesc_index::ihalo
integer, public ihalo
Definition: scale_atmos_grid_cartesC_index.F90:44
scale_atmos_grid_cartesc::atmos_grid_cartesc_generate
subroutine, public atmos_grid_cartesc_generate(DZ, DX, DY, FZ, FZ_MAX, OFFSET_X, OFFSET_Y, BUFFER_DZ, BUFFER_DX, BUFFER_DY, BUFFER_NZ, BUFFER_NX, BUFFER_NY, BUFFFACT, BUFFFACT_Z, BUFFFACT_X, BUFFFACT_Y)
Generate horizontal&vertical grid.
Definition: scale_atmos_grid_cartesC.F90:427
scale_file::file_open
subroutine, public file_open(basename, fid, mode, single, allnodes, aggregate, rankid, postfix)
Definition: scale_file.F90:536
scale_atmos_grid_cartesc::atmos_grid_cartesc_rfdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rfdx
reciprocal of face-dx
Definition: scale_atmos_grid_cartesC.F90:68
scale_atmos_grid_cartesc::atmos_grid_cartesc_setup
subroutine, public atmos_grid_cartesc_setup(basename, aggregate)
Setup.
Definition: scale_atmos_grid_cartesC.F90:109
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
scale_atmos_grid_cartesc::atmos_grid_cartesc_rcdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rcdx
reciprocal of center-dx
Definition: scale_atmos_grid_cartesC.F90:66
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdyg
center coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:82
scale_atmos_grid_cartesc::atmos_grid_cartesc_lcz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_lcz
center coordinate [m]: z, local land
Definition: scale_atmos_grid_cartesC.F90:51
scale_atmos_grid_cartesc::atmos_grid_cartesc_fyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fyg
face coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:79
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdy
y-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:62
scale_atmos_grid_cartesc::atmos_grid_cartesc_fx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fx
face coordinate [m]: x, local
Definition: scale_atmos_grid_cartesC.F90:58
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdyg
center coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:84
scale_prc::prc_myrank
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:91
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdy
y-length of grid(j+1) to grid(j) [m]
Definition: scale_atmos_grid_cartesC.F90:64
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfx
face buffer factor (0-1): x
Definition: scale_atmos_grid_cartesC.F90:73
scale_atmos_grid_cartesc_index::imaxg
integer, public imaxg
Definition: scale_atmos_grid_cartesC_index.F90:72
scale_atmos_grid_cartesc::atmos_grid_cartesc_rcdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rcdz
reciprocal of center-dz
Definition: scale_atmos_grid_cartesC.F90:45
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdxg
center coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:81
scale_atmos_grid_cartesc::dx
real(rp), public dx
Definition: scale_atmos_grid_cartesC.F90:39
scale_file
module file
Definition: scale_file.F90:15
scale_atmos_grid_cartesc_index::imax
integer, public imax
Definition: scale_atmos_grid_cartesC_index.F90:37
scale_atmos_grid_cartesc::atmos_grid_cartesc_domain_center_y
real(rp), public atmos_grid_cartesc_domain_center_y
center position of global domain [m]: y
Definition: scale_atmos_grid_cartesC.F90:92
scale_atmos_grid_cartesc_index::jmaxg
integer, public jmaxg
Definition: scale_atmos_grid_cartesC_index.F90:73
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfx
center buffer factor (0-1): x
Definition: scale_atmos_grid_cartesC.F90:71
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfxg
face buffer factor (0-1): x, global
Definition: scale_atmos_grid_cartesC.F90:88
scale_io
module STDIO
Definition: scale_io.F90:10
scale_atmos_grid_cartesc_index::jag
integer, public jag
Definition: scale_atmos_grid_cartesC_index.F90:75
scale_atmos_grid_cartesc::atmos_grid_cartesc_rcdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rcdy
reciprocal of center-dy
Definition: scale_atmos_grid_cartesC.F90:67
scale_atmos_grid_cartesc_index::iag
integer, public iag
Definition: scale_atmos_grid_cartesC_index.F90:74
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfz
center buffer factor (0-1): z
Definition: scale_atmos_grid_cartesC.F90:47
scale_atmos_grid_cartesc::atmos_grid_cartesc_cxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cxg
center coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:76
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:45
scale_atmos_grid_cartesc::atmos_grid_cartesc_domain_center_x
real(rp), public atmos_grid_cartesc_domain_center_x
center position of global domain [m]: x
Definition: scale_atmos_grid_cartesC.F90:91
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfy
face buffer factor (0-1): y
Definition: scale_atmos_grid_cartesC.F90:74
scale_prc_cartesc::prc_2drank
integer, dimension(:,:), allocatable, public prc_2drank
node index in 2D topology
Definition: scale_prc_cartesC.F90:45
scale_atmos_grid_cartesc_index::kmax
integer, public kmax
Definition: scale_atmos_grid_cartesC_index.F90:36
scale_atmos_grid_cartesc::atmos_grid_cartesc_fy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fy
face coordinate [m]: y, local
Definition: scale_atmos_grid_cartesC.F90:59
scale_prc_cartesc
module process / cartesC
Definition: scale_prc_cartesC.F90:11
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfz
face buffer factor (0-1): z
Definition: scale_atmos_grid_cartesC.F90:48
scale_atmos_grid_cartesc::atmos_grid_cartesc_output_info
subroutine atmos_grid_cartesc_output_info
Output information.
Definition: scale_atmos_grid_cartesC.F90:1008
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_atmos_grid_cartesc_index::is
integer, public is
start point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:53
scale_atmos_grid_cartesc_index::jhalo
integer, public jhalo
Definition: scale_atmos_grid_cartesC_index.F90:45
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfxg
center buffer factor (0-1): x, global
Definition: scale_atmos_grid_cartesC.F90:86
scale_atmos_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdx
x-length of grid(i+1) to grid(i) [m]
Definition: scale_atmos_grid_cartesC.F90:63
scale_atmos_grid_cartesc::atmos_grid_cartesc_lfz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_lfz
face coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:52
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfyg
face buffer factor (0-1): y, global
Definition: scale_atmos_grid_cartesC.F90:89
scale_atmos_grid_cartesc::dy
real(rp), public dy
Definition: scale_atmos_grid_cartesC.F90:39
scale_atmos_grid_cartesc::atmos_grid_cartesc_fxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fxg
face coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:78
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
scale_file::file_aggregate
logical, public file_aggregate
Definition: scale_file.F90:196
scale_atmos_grid_cartesc::atmos_grid_cartesc_fz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fz
face coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:42
scale_atmos_grid_cartesc::atmos_grid_cartesc_name
character(len=7), parameter, public atmos_grid_cartesc_name
Definition: scale_atmos_grid_cartesC.F90:37
scale_atmos_grid_cartesc::atmos_grid_cartesc_cyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cyg
center coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:77
scale_atmos_grid_cartesc_index::jmax
integer, public jmax
Definition: scale_atmos_grid_cartesC_index.F90:38
scale_atmos_grid_cartesc_index::js
integer, public js
start point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:55
scale_prc_cartesc::prc_num_y
integer, public prc_num_y
y length of 2D processor topology
Definition: scale_prc_cartesC.F90:43
scale_atmos_grid_cartesc::atmos_grid_cartesc_cy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cy
center coordinate [m]: y, local
Definition: scale_atmos_grid_cartesC.F90:57
scale_atmos_grid_cartesc::atmos_grid_cartesc_finalize
subroutine, public atmos_grid_cartesc_finalize
Definition: scale_atmos_grid_cartesC.F90:214
scale_atmos_grid_cartesc::atmos_grid_cartesc_rfdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rfdz
reciprocal of face-dz
Definition: scale_atmos_grid_cartesC.F90:46
scale_atmos_grid_cartesc::atmos_grid_cartesc_allocate
subroutine, public atmos_grid_cartesc_allocate
Definition: scale_atmos_grid_cartesC.F90:277
scale_atmos_grid_cartesc::atmos_grid_cartesc_lcdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_lcdz
z-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:53
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfy
center buffer factor (0-1): y
Definition: scale_atmos_grid_cartesC.F90:72
scale_prc_cartesc::prc_num_x
integer, public prc_num_x
x length of 2D processor topology
Definition: scale_prc_cartesC.F90:42
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdx
x-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:61
scale_atmos_grid_cartesc
module atmosphere / grid / cartesC
Definition: scale_atmos_grid_cartesC.F90:12
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdz
z-length of grid(i+1) to grid(i) [m]
Definition: scale_atmos_grid_cartesC.F90:44
scale_atmos_grid_cartesc::dz
real(rp), public dz
Definition: scale_atmos_grid_cartesC.F90:39
scale_atmos_grid_cartesc::atmos_grid_cartesc_cz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:41
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfyg
center buffer factor (0-1): y, global
Definition: scale_atmos_grid_cartesC.F90:87
scale_atmos_grid_cartesc::atmos_grid_cartesc_rfdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rfdy
reciprocal of face-dy
Definition: scale_atmos_grid_cartesC.F90:69
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:57
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
scale_atmos_grid_cartesc::atmos_grid_cartesc_cx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cx
center coordinate [m]: x, local
Definition: scale_atmos_grid_cartesC.F90:56
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdxg
center coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:83