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
31 
32  !-----------------------------------------------------------------------------
33  !
34  !++ Public parameters & variables
35  !
36  character(len=7), public, parameter :: atmos_grid_cartesc_name = 'cartesC'
37 
38  real(rp), public :: dz, dx, dy
39 
40  real(rp), public, allocatable :: atmos_grid_cartesc_cz (:)
41  real(rp), public, allocatable :: atmos_grid_cartesc_fz (:)
42  real(rp), public, allocatable :: atmos_grid_cartesc_cdz (:)
43  real(rp), public, allocatable :: atmos_grid_cartesc_fdz (:)
44  real(rp), public, allocatable :: atmos_grid_cartesc_rcdz (:)
45  real(rp), public, allocatable :: atmos_grid_cartesc_rfdz (:)
46  real(rp), public, allocatable :: atmos_grid_cartesc_cbfz (:)
47  real(rp), public, allocatable :: atmos_grid_cartesc_fbfz (:)
48 
49  ! land
50  real(rp), public, allocatable :: atmos_grid_cartesc_lcz (:)
51  real(rp), public, allocatable :: atmos_grid_cartesc_lfz (:)
52  real(rp), public, allocatable :: atmos_grid_cartesc_lcdz(:)
53 
54  ! horizontal
55  real(rp), public, allocatable :: atmos_grid_cartesc_cx (:)
56  real(rp), public, allocatable :: atmos_grid_cartesc_cy (:)
57  real(rp), public, allocatable :: atmos_grid_cartesc_fx (:)
58  real(rp), public, allocatable :: atmos_grid_cartesc_fy (:)
59 
60  real(rp), public, allocatable :: atmos_grid_cartesc_cdx (:)
61  real(rp), public, allocatable :: atmos_grid_cartesc_cdy (:)
62  real(rp), public, allocatable :: atmos_grid_cartesc_fdx (:)
63  real(rp), public, allocatable :: atmos_grid_cartesc_fdy (:)
64 
65  real(rp), public, allocatable :: atmos_grid_cartesc_rcdx (:)
66  real(rp), public, allocatable :: atmos_grid_cartesc_rcdy (:)
67  real(rp), public, allocatable :: atmos_grid_cartesc_rfdx (:)
68  real(rp), public, allocatable :: atmos_grid_cartesc_rfdy (:)
69 
70  real(rp), public, allocatable :: atmos_grid_cartesc_cbfx (:)
71  real(rp), public, allocatable :: atmos_grid_cartesc_cbfy (:)
72  real(rp), public, allocatable :: atmos_grid_cartesc_fbfx (:)
73  real(rp), public, allocatable :: atmos_grid_cartesc_fbfy (:)
74 
75  real(rp), public, allocatable :: atmos_grid_cartesc_cxg (:)
76  real(rp), public, allocatable :: atmos_grid_cartesc_cyg (:)
77  real(rp), public, allocatable :: atmos_grid_cartesc_fxg (:)
78  real(rp), public, allocatable :: atmos_grid_cartesc_fyg (:)
79 
80  real(rp), public, allocatable :: atmos_grid_cartesc_cdxg (:)
81  real(rp), public, allocatable :: atmos_grid_cartesc_cdyg (:)
82  real(rp), public, allocatable :: atmos_grid_cartesc_fdxg (:)
83  real(rp), public, allocatable :: atmos_grid_cartesc_fdyg (:)
84 
85  real(rp), public, allocatable :: atmos_grid_cartesc_cbfxg(:)
86  real(rp), public, allocatable :: atmos_grid_cartesc_cbfyg(:)
87  real(rp), public, allocatable :: atmos_grid_cartesc_fbfxg(:)
88  real(rp), public, allocatable :: atmos_grid_cartesc_fbfyg(:)
89 
92 
93  !-----------------------------------------------------------------------------
94  !
95  !++ Private procedure
96  !
97  !-----------------------------------------------------------------------------
98  !
99  !++ Private parameters & variables
100  !
101  !-----------------------------------------------------------------------------
102 contains
103  !-----------------------------------------------------------------------------
105  subroutine atmos_grid_cartesc_setup( &
106  basename, &
107  aggregate )
108  use scale_prc, only: &
109  prc_abort
110  use scale_file, only: &
112  implicit none
113  character(len=*), intent(in), optional :: basename
114  logical, intent(in), optional :: aggregate
115 
116  character(len=H_LONG) :: atmos_grid_cartesc_in_basename = ''
117  logical :: atmos_grid_cartesc_in_aggregate
118 
119  real(rp) :: offset_x = 0.0_rp
120  real(rp) :: offset_y = 0.0_rp
121 
122  real(rp) :: buffer_dz = 0.0_rp
123  real(rp) :: buffer_dx = 0.0_rp
124  real(rp) :: buffer_dy = 0.0_rp
125  real(rp) :: bufffact = 1.0_rp
126  real(rp) :: bufffact_z = -1.0_rp
127  real(rp) :: bufffact_x = -1.0_rp
128  real(rp) :: bufffact_y = -1.0_rp
129 
130  integer :: buffer_nz = -1
131  integer :: buffer_nx = -1
132  integer :: buffer_ny = -1
133 
134  integer, parameter :: fz_max = 300
135  real(rp) :: fz(fz_max)
136 
137  namelist / param_atmos_grid_cartesc / &
138  atmos_grid_cartesc_in_basename, &
139  atmos_grid_cartesc_in_aggregate, &
140  dz, &
141  dx, &
142  dy, &
143  buffer_dz, &
144  buffer_dx, &
145  buffer_dy, &
146  buffer_nz, &
147  buffer_nx, &
148  buffer_ny, &
149  bufffact, &
150  bufffact_z, &
151  bufffact_x, &
152  bufffact_y, &
153  fz, &
154  offset_x, &
155  offset_y
156 
157  integer :: ierr
158  !---------------------------------------------------------------------------
159 
160  log_newline
161  log_info("ATMOS_GRID_CARTESC_setup",*) 'Setup'
162 
163  if ( kmax < 1 ) then
164  log_info("ATMOS_GRID_CARTESC_setup",*) 'Skip because KMAX < 1'
165  return
166  end if
167 
168  fz(:) = -1.0_rp
169 
170  if ( present(basename) ) atmos_grid_cartesc_in_basename = basename
171  if ( present(aggregate) ) then
172  atmos_grid_cartesc_in_aggregate = aggregate
173  else
174  atmos_grid_cartesc_in_aggregate = file_aggregate
175  end if
176 
177  !--- read namelist
178  rewind(io_fid_conf)
179  read(io_fid_conf,nml=param_atmos_grid_cartesc,iostat=ierr)
180  if( ierr < 0 ) then !--- missing
181  log_info("ATMOS_GRID_CARTESC_setup",*) 'Not found namelist. Default used.'
182  elseif( ierr > 0 ) then !--- fatal error
183  log_error("ATMOS_GRID_CARTESC_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_GRID_CARTESC. Check!'
184  call prc_abort
185  endif
186  log_nml(param_atmos_grid_cartesc)
187 
188 
190 
191  if ( atmos_grid_cartesc_in_basename /= '' ) then
192 
193  call atmos_grid_cartesc_read( atmos_grid_cartesc_in_basename, atmos_grid_cartesc_in_aggregate )
194 
195  else
196 
198  dz, dx, dy, fz(:), fz_max, &
199  offset_x, offset_y, &
200  buffer_dz, buffer_dx, buffer_dy, &
201  buffer_nz, buffer_nx, buffer_ny, &
202  bufffact, &
203  bufffact_z, bufffact_x, bufffact_y )
204 
205  end if
206 
208 
209  return
210  end subroutine atmos_grid_cartesc_setup
211 
212  !-----------------------------------------------------------------------------
213  ! private
214  !-----------------------------------------------------------------------------
215 
216  subroutine atmos_grid_cartesc_allocate
217  implicit none
218  !---------------------------------------------------------------------------
219 
220  ! local domain
221  allocate( atmos_grid_cartesc_cz( ka) )
222  allocate( atmos_grid_cartesc_cx( ia) )
223  allocate( atmos_grid_cartesc_cy( ja) )
224  allocate( atmos_grid_cartesc_fz(0:ka) )
225  allocate( atmos_grid_cartesc_fx(0:ia) )
226  allocate( atmos_grid_cartesc_fy(0:ja) )
227 
228  allocate( atmos_grid_cartesc_cdz(ka) )
229  allocate( atmos_grid_cartesc_cdx(ia) )
230  allocate( atmos_grid_cartesc_cdy(ja) )
231  allocate( atmos_grid_cartesc_fdz(ka-1) )
232  allocate( atmos_grid_cartesc_fdx(ia-1) )
233  allocate( atmos_grid_cartesc_fdy(ja-1) )
234 
235  allocate( atmos_grid_cartesc_rcdz(ka) )
236  allocate( atmos_grid_cartesc_rcdx(ia) )
237  allocate( atmos_grid_cartesc_rcdy(ja) )
238  allocate( atmos_grid_cartesc_rfdz(ka-1) )
239  allocate( atmos_grid_cartesc_rfdx(ia-1) )
240  allocate( atmos_grid_cartesc_rfdy(ja-1) )
241 
242  allocate( atmos_grid_cartesc_cbfz( ka) )
243  allocate( atmos_grid_cartesc_cbfx( ia) )
244  allocate( atmos_grid_cartesc_cbfy( ja) )
245  allocate( atmos_grid_cartesc_fbfz(0:ka) )
246  allocate( atmos_grid_cartesc_fbfx(0:ia) )
247  allocate( atmos_grid_cartesc_fbfy(0:ja) )
248 
249  ! global domain
250  allocate( atmos_grid_cartesc_cxg( iag) )
251  allocate( atmos_grid_cartesc_cyg( jag) )
252  allocate( atmos_grid_cartesc_fxg(0:iag) )
253  allocate( atmos_grid_cartesc_fyg(0:jag) )
254 
255  allocate( atmos_grid_cartesc_cdxg(iag) )
256  allocate( atmos_grid_cartesc_cdyg(jag) )
257  allocate( atmos_grid_cartesc_fdxg(iag-1) )
258  allocate( atmos_grid_cartesc_fdyg(jag-1) )
259 
260  allocate( atmos_grid_cartesc_cbfxg( iag) )
261  allocate( atmos_grid_cartesc_cbfyg( jag) )
262  allocate( atmos_grid_cartesc_fbfxg(0:iag) )
263  allocate( atmos_grid_cartesc_fbfyg(0:jag) )
264 
265  return
266  end subroutine atmos_grid_cartesc_allocate
267 
268  !-----------------------------------------------------------------------------
270  subroutine atmos_grid_cartesc_read( &
271  basename, aggregate )
272  use scale_file, only: &
273  file_open, &
274  file_read
275  use scale_prc, only: &
276  prc_myrank
277  implicit none
278 
279  character(len=*), intent(in) :: basename
280  logical, intent(in), optional :: aggregate
281 
282  integer :: fid
283 
284  real(rp) :: fdxg(0:iag), fdyg(0:jag)
285  real(rp) :: fdx(0:ia), fdy(0:ja)
286  !---------------------------------------------------------------------------
287 
288 
289  call file_open( basename, fid, rankid=prc_myrank, aggregate=aggregate )
290 
291  call file_read( fid, 'CZ', atmos_grid_cartesc_cz(:) )
292  call file_read( fid, 'CX', atmos_grid_cartesc_cx(:) )
293  call file_read( fid, 'CY', atmos_grid_cartesc_cy(:) )
294 
295  call file_read( fid, 'FZ', atmos_grid_cartesc_fz(:) )
296  call file_read( fid, 'FX', atmos_grid_cartesc_fx(:) )
297  call file_read( fid, 'FY', atmos_grid_cartesc_fy(:) )
298 
299  call file_read( fid, 'CDZ', atmos_grid_cartesc_cdz(:) )
300  call file_read( fid, 'CDX', atmos_grid_cartesc_cdx(:) )
301  call file_read( fid, 'CDY', atmos_grid_cartesc_cdy(:) )
302 
303  call file_read( fid, 'FDZ', atmos_grid_cartesc_fdz(:) )
304  call file_read( fid, 'FDX', fdx(:) )
305  call file_read( fid, 'FDY', fdy(:) )
306  atmos_grid_cartesc_fdx(:) = fdx(1:ia-1)
307  atmos_grid_cartesc_fdy(:) = fdy(1:ja-1)
308 
315 
316  call file_read( fid, 'CBFZ', atmos_grid_cartesc_cbfz(:) )
317  call file_read( fid, 'CBFX', atmos_grid_cartesc_cbfx(:) )
318  call file_read( fid, 'CBFY', atmos_grid_cartesc_cbfy(:) )
319  call file_read( fid, 'FBFZ', atmos_grid_cartesc_fbfz(:) )
320  call file_read( fid, 'FBFX', atmos_grid_cartesc_fbfx(:) )
321  call file_read( fid, 'FBFY', atmos_grid_cartesc_fbfy(:) )
322 
323  call file_read( fid, 'CXG', atmos_grid_cartesc_cxg(:) )
324  call file_read( fid, 'CYG', atmos_grid_cartesc_cyg(:) )
325  call file_read( fid, 'FXG', atmos_grid_cartesc_fxg(:) )
326  call file_read( fid, 'FYG', atmos_grid_cartesc_fyg(:) )
327 
328  call file_read( fid, 'CDXG', atmos_grid_cartesc_cdxg(:) )
329  call file_read( fid, 'CDYG', atmos_grid_cartesc_cdyg(:) )
330  call file_read( fid, 'FDXG', fdxg(:) )
331  call file_read( fid, 'FDYG', fdyg(:) )
332  atmos_grid_cartesc_fdxg(:) = fdxg(1:ia-1)
333  atmos_grid_cartesc_fdyg(:) = fdyg(1:ja-1)
334 
335 
338 
339  return
340  end subroutine atmos_grid_cartesc_read
341 
342  !-----------------------------------------------------------------------------
344  subroutine atmos_grid_cartesc_generate( &
345  DZ, DX, DY, FZ, FZ_MAX, &
346  OFFSET_X, OFFSET_Y, &
347  BUFFER_DZ, BUFFER_DX, BUFFER_DY, &
348  BUFFER_NZ, BUFFER_NX, BUFFER_NY, &
349  BUFFFACT, &
350  BUFFFACT_Z, BUFFFACT_X, BUFFFACT_Y )
351  use scale_prc, only: &
352  prc_abort, &
353  prc_myrank
354  use scale_prc_cartesc, only: &
355  prc_2drank, &
356  prc_num_x, &
357  prc_num_y
358  implicit none
359  real(rp), intent(in) :: dz, dx, dy
360  real(rp), intent(in), optional :: fz(:)
361  integer, intent(in), optional :: fz_max
362  real(rp), intent(in), optional :: offset_x, offset_y
363  real(rp), intent(in), optional :: buffer_dz, buffer_dx, buffer_dy
364  integer, intent(in), optional :: buffer_nz, buffer_nx, buffer_ny
365  real(rp), intent(in), optional :: bufffact
366  real(rp), intent(in), optional :: bufffact_z, bufffact_x, bufffact_y
367 
368  real(rp), allocatable :: buffz(:), buffx(:), buffy(:)
369  real(rp) :: bufftotz, bufftotx, bufftoty
370  real(rp) :: fact
371 
372  integer :: kbuff, ibuff, jbuff
373  integer :: kmain, imain, jmain
374 
375  real(rp) :: dz_tmp
376 
377  logical :: use_user_input
378 
379  integer :: k, i, j, ii, jj
380  !---------------------------------------------------------------------------
381 
382  !##### coordinate in global domain #####
383 
384  allocate( buffx(0:iag) )
385  allocate( buffy(0:jag) )
386 
387 
388  ! X-direction
389  ! calculate buffer grid size
390 
391  fact = -1.0_rp
392  if ( present(bufffact_x) ) fact = bufffact_x
393  if ( fact < 0.0_rp .and. present(bufffact) ) fact = bufffact
394  if ( fact < 0.0_rp ) fact = 1.0_rp
395 
396  buffx(0) = dx
397  bufftotx = 0.0_rp
398  ibuff = -1
399  if ( present(buffer_nx) ) ibuff = buffer_nx
400  if ( ibuff > 0 ) then
401  if ( 2*ibuff > imaxg ) then
402  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', ibuff, &
403  'x2) must be smaller than global domain size (X). Use smaller BUFFER_NX!'
404  call prc_abort
405  endif
406 
407  do i = 1, ibuff
408  buffx(i) = buffx(i-1) * fact
409  bufftotx = bufftotx + buffx(i)
410  enddo
411  imain = imaxg - 2*ibuff
412  else if ( present(buffer_dz) ) then
413  do i = 1, iag
414  if( bufftotx >= buffer_dx ) exit
415  buffx(i) = buffx(i-1) * fact
416  bufftotx = bufftotx + buffx(i)
417  enddo
418  ibuff = i - 1
419  imain = imaxg - 2*ibuff
420 
421  if ( imain < 0 ) then
422  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', bufftotx, &
423  'x2[m]) must be smaller than global domain size (X). Use smaller BUFFER_DX!'
424  call prc_abort
425  endif
426  else
427  ibuff = 0
428  imain = imaxg
429  endif
430 
431  ! horizontal coordinate (global domain)
432  if ( present(offset_x) ) then
433  atmos_grid_cartesc_fxg(ihalo) = offset_x
434  else
435  atmos_grid_cartesc_fxg(ihalo) = 0.0_rp
436  end if
437  do i = ihalo-1, 0, -1
438  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i+1) - buffx(ibuff)
439  enddo
440 
441  do i = 1, ihalo
443  enddo
444 
445  if ( ibuff > 0 ) then
446  do i = ihalo+1, ihalo+ibuff
447  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i-1) + buffx(ibuff+ihalo+1-i)
449  enddo
450  endif
451 
452  do i = ihalo+ibuff+1, ihalo+ibuff+imain
455  enddo
456 
457  if ( ibuff > 0 ) then
458  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
459  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i-1) + buffx(i-ihalo-ibuff-imain)
461  enddo
462  endif
463 
464  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
465  atmos_grid_cartesc_fxg(i) = atmos_grid_cartesc_fxg(i-1) + buffx(ibuff)
467  enddo
468 
469  do i = 1, iag
471  end do
472  do i = 1, iag-1
474  end do
475 
476  ! calc buffer factor (global domain)
477  atmos_grid_cartesc_cbfxg(:) = 0.0_rp
478  atmos_grid_cartesc_fbfxg(:) = 0.0_rp
479  do i = 1, ihalo
480  atmos_grid_cartesc_cbfxg(i) = 1.0_rp
481  enddo
482  do i = 0, ihalo
483  atmos_grid_cartesc_fbfxg(i) = 1.0_rp
484  enddo
485 
486  if ( ibuff > 0 ) then
487  do i = ihalo+1, ihalo+ibuff
490  enddo
491 
492  do i = ihalo+ibuff+imain+1, ihalo+ibuff+imain+ibuff
495  enddo
496  endif
497 
498  do i = ihalo+ibuff+imain+ibuff+1, ihalo+ibuff+imain+ibuff+ihalo
499  atmos_grid_cartesc_cbfxg(i) = 1.0_rp
500  atmos_grid_cartesc_fbfxg(i) = 1.0_rp
501  enddo
502 
503  atmos_grid_cartesc_cbfxg(:) = max( min( atmos_grid_cartesc_cbfxg(:), 1.0_rp ), 0.0_rp )
504  atmos_grid_cartesc_fbfxg(:) = max( min( atmos_grid_cartesc_fbfxg(:), 1.0_rp ), 0.0_rp )
505 
506  ! Y-direction
507  ! calculate buffer grid size
508 
509  fact = -1.0_rp
510  if ( present(bufffact_y) ) fact = bufffact_y
511  if ( fact < 0.0_rp .and. present(bufffact) )fact = bufffact
512  if ( fact < 0.0_rp ) fact = 1.0_rp
513 
514  buffy(0) = dy
515  bufftoty = 0.0_rp
516  jbuff = -1
517  if ( present(buffer_ny) ) jbuff = buffer_ny
518  if ( jbuff > 0 ) then
519  if ( 2*jbuff > jmaxg ) then
520  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', jbuff, &
521  'x2) must be smaller than global domain size (Y). Use smaller BUFFER_NY!'
522  call prc_abort
523  endif
524 
525  do j = 1, jbuff
526  buffy(j) = buffy(j-1) * fact
527  bufftoty = bufftoty + buffy(j)
528  enddo
529  jmain = jmaxg - 2*jbuff
530  else if ( present(buffer_dy) ) then
531  do j = 1, jag
532  if( bufftoty >= buffer_dy ) exit
533  buffy(j) = buffy(j-1) * fact
534  bufftoty = bufftoty + buffy(j)
535  enddo
536  jbuff = j - 1
537  jmain = jmaxg - 2*jbuff
538 
539  if ( jmain < 0 ) then
540  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', bufftoty, &
541  'x2[m]) must be smaller than global domain size (Y). Use smaller BUFFER_DY!'
542  call prc_abort
543  endif
544  else
545  jbuff = 0
546  jmain = jmaxg
547  endif
548 
549  ! horizontal coordinate (global domain)
550  if ( present(offset_y) ) then
551  atmos_grid_cartesc_fyg(jhalo) = offset_y
552  else
553  atmos_grid_cartesc_fyg(jhalo) = 0.0_rp
554  end if
555  do j = jhalo-1, 0, -1
556  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j+1) - buffy(jbuff)
557  enddo
558 
559  do j = 1, jhalo
561  enddo
562 
563  if ( jbuff > 0 ) then
564  do j = jhalo+1, jhalo+jbuff
565  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j-1) + buffy(jbuff+jhalo+1-j)
567  enddo
568  endif
569 
570  do j = jhalo+jbuff+1, jhalo+jbuff+jmain
573  enddo
574 
575  if ( jbuff > 0 ) then
576  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
577  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j-1) + buffy(j-jhalo-jbuff-jmain)
579  enddo
580  endif
581 
582  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
583  atmos_grid_cartesc_fyg(j) = atmos_grid_cartesc_fyg(j-1) + buffy(jbuff)
585  enddo
586 
587  do j = 1, jag
589  end do
590  do j = 1, jag-1
592  end do
593 
594  ! calc buffer factor (global domain)
595  atmos_grid_cartesc_cbfyg(:) = 0.0_rp
596  atmos_grid_cartesc_fbfyg(:) = 0.0_rp
597  do j = 1, jhalo
598  atmos_grid_cartesc_cbfyg(j) = 1.0_rp
599  enddo
600  do j = 0, jhalo
601  atmos_grid_cartesc_fbfyg(j) = 1.0_rp
602  enddo
603 
604  if ( jbuff > 0 ) then
605  do j = jhalo+1, jhalo+jbuff
608  enddo
609 
610  do j = jhalo+jbuff+jmain+1, jhalo+jbuff+jmain+jbuff
613  enddo
614  endif
615 
616  do j = jhalo+jbuff+jmain+jbuff+1, jhalo+jbuff+jmain+jbuff+jhalo
617  atmos_grid_cartesc_cbfyg(j) = 1.0_rp
618  atmos_grid_cartesc_fbfyg(j) = 1.0_rp
619  enddo
620  atmos_grid_cartesc_cbfyg(:) = max( min( atmos_grid_cartesc_cbfyg(:), 1.0_rp ), 0.0_rp )
621  atmos_grid_cartesc_fbfyg(:) = max( min( atmos_grid_cartesc_fbfyg(:), 1.0_rp ), 0.0_rp )
622 
623  deallocate( buffx )
624  deallocate( buffy )
625 
626  !##### coordinate in local domain #####
627 
628  allocate( buffz(0:ka) )
629 
630  use_user_input = .false.
631  if ( present(fz) ) then
632  if ( maxval(fz(:)) > 0.0_rp ) then ! try to use input from namelist
633  log_info("ATMOS_GRID_CARTESC_generate",*) 'Z coordinate is given from NAMELIST.'
634 
635  if ( kmax < 2 ) then
636  log_error("ATMOS_GRID_CARTESC_generate",*) 'KMAX must be larger than 1. Check!', kmax
637  call prc_abort
638  endif
639 
640  if ( kmax > fz_max ) then
641  log_error("ATMOS_GRID_CARTESC_generate",*) 'KMAX must be smaller than ', fz_max, '. Check!', kmax
642  call prc_abort
643  endif
644 
645  if ( minval(fz(1:kmax)) <= 0.0_rp ) then
646  log_error("ATMOS_GRID_CARTESC_generate",*) 'FZ must be positive. Check! minval(FZ(1:KMAX))=', minval(fz(1:kmax))
647  call prc_abort
648  endif
649 
650  use_user_input = .true.
651  endif
652  end if
653 
654  if ( use_user_input ) then ! input from namelist
655 
656  ! Z-direction
657  ! calculate buffer grid size
658 
659  kbuff = -1
660  if ( present(buffer_nz) ) kbuff = buffer_nz
661  if ( kbuff > 0 ) then
662  if ( kbuff > kmax ) then
663  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', kbuff, &
664  ') must be smaller than global domain size (Z). Use smaller BUFFER_NZ!'
665  call prc_abort
666  endif
667 
668  bufftotz = 0.0_rp
669  do k = kmax, kmax-kbuff+1, -1
670  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
671  enddo
672  kmain = kmax - kbuff
673  else if ( present(buffer_dz) ) then
674  if ( buffer_dz > fz(kmax) ) then
675  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', buffer_dz, &
676  '[m]) must be smaller than global domain size (Z). Use smaller BUFFER_DZ!'
677  call prc_abort
678  endif
679 
680  bufftotz = 0.0_rp
681  do k = kmax, 2, -1
682  if( bufftotz >= buffer_dz ) exit
683  bufftotz = bufftotz + ( fz(k) - fz(k-1) )
684  enddo
685  kbuff = kmax - k
686  kmain = k
687  else
688  bufftotz = 0.0_rp
689  kbuff = 0
690  kmain = kmax
691  endif
692 
693  ! vertical coordinate (local=global domain)
694  atmos_grid_cartesc_fz(ks-1) = 0.0_rp
695 
696  dz_tmp = fz(1)
697  do k = ks-2, 0, -1
699  enddo
700 
701  do k = ks, ke
702  atmos_grid_cartesc_fz(k) = fz(k-ks+1)
703  enddo
704 
705  dz_tmp = fz(kmax) - fz(kmax-1)
706  do k = ke+1, ka
708  enddo
709 
710  do k = 1, ka
712  enddo
713 
714  else ! calc using DZ
715 
716  ! Z-direction
717  ! calculate buffer grid size
718 
719  fact = -1.0_rp
720  if ( present(bufffact_z) ) fact = bufffact_z
721  if ( fact < 0.0_rp .and. present(bufffact) ) fact = bufffact
722  if ( fact < 0.0_rp ) fact = 1.0_rp
723 
724  buffz(0) = dz
725  bufftotz = 0.0_rp
726  kbuff = -1
727  if ( present(buffer_nz) ) kbuff = buffer_nz
728  if ( kbuff > 0 ) then
729  if ( kbuff > kmax ) then
730  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer grid size (', kbuff, &
731  ') must be smaller than global domain size (Z). Use smaller BUFFER_NZ!'
732  call prc_abort
733  endif
734 
735  do k = 1, kbuff
736  buffz(k) = buffz(k-1) * fact
737  bufftotz = bufftotz + buffz(k)
738  enddo
739  kmain = kmax - kbuff
740  else if ( present(buffer_dz) ) then
741  do k = 1, ka
742  if( bufftotz >= buffer_dz ) exit
743  buffz(k) = buffz(k-1) * fact
744  bufftotz = bufftotz + buffz(k)
745  enddo
746  kbuff = k - 1
747  kmain = kmax - kbuff
748 
749  if ( kmain < 0 ) then
750  log_error("ATMOS_GRID_CARTESC_generate",*) 'Buffer length (', bufftotz, &
751  '[m]) must be smaller than global domain size (Z). Use smaller BUFFER_DZ!'
752  call prc_abort
753  endif
754  else
755  kbuff = 0
756  kmain = kmax
757  endif
758 
759  ! vertical coordinate (local=global domain)
760  atmos_grid_cartesc_fz(ks-1) = 0.0_rp
761  do k = ks-2, 0, -1
763  enddo
764 
765  do k = 1, ks-1
767  enddo
768 
769  do k = ks, ks+kmain-1
772  enddo
773 
774  if ( kbuff > 0 ) then
775  do k = ks+kmain, ke
776  atmos_grid_cartesc_fz(k) = atmos_grid_cartesc_fz(k-1) + buffz(k-ks-kmain+1)
778  enddo
779  endif
780 
781  do k = ke+1, ka
782  atmos_grid_cartesc_fz(k) = atmos_grid_cartesc_fz(k-1) + buffz(kbuff)
784  enddo
785 
786  endif
787 
788  ! calc buffer factor (global domain)
789  atmos_grid_cartesc_cbfz(:) = 0.0_rp
790  atmos_grid_cartesc_fbfz(:) = 0.0_rp
791  if ( kbuff > 0 ) then
792  do k = ks+kmain, ke
795  enddo
796  endif
797 
798  do k = ke+1, ka
799  atmos_grid_cartesc_cbfz(k) = 1.0_rp
800  atmos_grid_cartesc_fbfz(k) = 1.0_rp
801  enddo
802  atmos_grid_cartesc_cbfz(:) = max( min( atmos_grid_cartesc_cbfz(:), 1.0_rp ), 0.0_rp )
803  atmos_grid_cartesc_fbfz(:) = max( min( atmos_grid_cartesc_fbfz(:), 1.0_rp ), 0.0_rp )
804 
805  deallocate( buffz )
806 
807  ! vertical coordinate (local domain)
808  do k = 1, ka
811  enddo
812 
813  do k = 1, ka-1
816  enddo
817 
818  ! X-direction
819  ! horizontal coordinate (local domain)
820  do i = 0, ia
821  ii = i + prc_2drank(prc_myrank,1) * imax
822 
824  enddo
825 
826  ii = prc_2drank(prc_myrank,1) * imax
828  do i = 1, ia
829  ii = i + prc_2drank(prc_myrank,1) * imax
830 
834 
837  enddo
838 
839  do i = 1, ia-1
842  enddo
843 
844  ! Y-direction
845  ! horizontal coordinate (local domain)
846  do j = 0, ja
847  jj = j + prc_2drank(prc_myrank,2) * jmax
848 
850  enddo
851 
852  jj = prc_2drank(prc_myrank,2) * jmax
854  do j = 1, ja
855  jj = j + prc_2drank(prc_myrank,2) * jmax
856 
860 
863  enddo
864 
865  do j = 1, ja-1
868  enddo
869 
872 
873  ! report
874  log_newline
875  log_info("ATMOS_GRID_CARTESC_generate",*) 'Grid information '
876  log_info_cont('(1x,A,3(1x,F9.3))') 'delta Z, X, Y [m] :', dz, dx, dy
877 
878  log_newline
879  log_info("ATMOS_GRID_CARTESC_generate",*) 'Main/buffer Grid (global) :'
880  log_info_cont('(1x,2(A,I6))') 'Z: buffer = ', kbuff,' x 1, main = ',kmain
881  log_info_cont('(1x,2(A,I6))') 'X: buffer = ', ibuff,' x 2, main = ',imain
882  log_info_cont('(1x,2(A,I6))') 'Y: buffer = ', jbuff,' x 2, main = ',jmain
883 
884  log_newline
885  log_info("ATMOS_GRID_CARTESC_generate",*) 'Domain size [km] (global) :'
886  log_info_cont('(1x,7(A,F9.3))') 'Z:', &
887  atmos_grid_cartesc_fz(0) *1.e-3_rp, ' -HALO- ', &
888  atmos_grid_cartesc_fz(ks-1) *1.e-3_rp, ' | ', &
889  atmos_grid_cartesc_cz(ks) *1.e-3_rp, ' - ', &
890  atmos_grid_cartesc_cz(ke-kbuff)*1.e-3_rp, ' | ', &
891  atmos_grid_cartesc_fz(ke-kbuff)*1.e-3_rp, ' -buffer- ', &
892  atmos_grid_cartesc_fz(ke) *1.e-3_rp, ' -HALO- ', &
893  atmos_grid_cartesc_fz(ka) *1.e-3_rp
894  log_info_cont('(1x,8(A,F9.3))') 'X:', &
895  atmos_grid_cartesc_fxg(0) *1.e-3_rp, ' -HALO- ', &
896  atmos_grid_cartesc_fxg(ihalo) *1.e-3_rp, ' -buffer- ', &
897  atmos_grid_cartesc_fxg(ihalo+ibuff) *1.e-3_rp, ' | ', &
898  atmos_grid_cartesc_cxg(ihalo+ibuff+1) *1.e-3_rp, ' - ', &
899  atmos_grid_cartesc_cxg(iag-ihalo-ibuff)*1.e-3_rp, ' | ', &
900  atmos_grid_cartesc_fxg(iag-ihalo-ibuff)*1.e-3_rp, ' -buffer- ', &
901  atmos_grid_cartesc_fxg(iag-ihalo) *1.e-3_rp, ' -HALO- ', &
902  atmos_grid_cartesc_fxg(iag) *1.e-3_rp
903  log_info_cont('(1x,8(A,F9.3))') 'Y:', &
904  atmos_grid_cartesc_fyg(0) *1.e-3_rp, ' -HALO- ', &
905  atmos_grid_cartesc_fyg(jhalo) *1.e-3_rp, ' -buffer- ', &
906  atmos_grid_cartesc_fyg(jhalo+jbuff) *1.e-3_rp, ' | ', &
907  atmos_grid_cartesc_cyg(jhalo+jbuff+1) *1.e-3_rp, ' - ', &
908  atmos_grid_cartesc_cyg(jag-jhalo-jbuff)*1.e-3_rp, ' | ', &
909  atmos_grid_cartesc_fyg(jag-jhalo-jbuff)*1.e-3_rp, ' -buffer- ', &
910  atmos_grid_cartesc_fyg(jag-jhalo) *1.e-3_rp, ' -HALO- ', &
911  atmos_grid_cartesc_fyg(jag) *1.e-3_rp
912 
913  return
914  end subroutine atmos_grid_cartesc_generate
915 
916  !-----------------------------------------------------------------------------
919  integer :: k
920 
921  log_newline
922  log_info("ATMOS_GRID_CARTESC_output_info",*) 'Center Position of Grid (global) :'
923  log_info_cont('(1x,A,F12.3)') 'X: ', atmos_grid_cartesc_domain_center_x
924  log_info_cont('(1x,A,F12.3)') 'Y: ', atmos_grid_cartesc_domain_center_y
925 
926 
927  log_newline
928  log_info("ATMOS_GRID_CARTESC_output_info",*) 'Domain size [km] (local) :'
929  log_info_cont('(1x,6(A,F9.3))') 'X:', &
930  atmos_grid_cartesc_fx(0) *1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fx(is-1)*1.e-3_rp, ' | ', &
931  atmos_grid_cartesc_cx(is)*1.e-3_rp, ' - ', atmos_grid_cartesc_cx(ie) *1.e-3_rp, ' | ', &
932  atmos_grid_cartesc_fx(ie)*1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fx(ia) *1.e-3_rp
933  log_info_cont('(1x,6(A,F9.3))') 'Y:', &
934  atmos_grid_cartesc_fy(0) *1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fy(js-1)*1.e-3_rp, ' | ', &
935  atmos_grid_cartesc_cy(js)*1.e-3_rp, ' - ', atmos_grid_cartesc_cy(je) *1.e-3_rp, ' | ', &
936  atmos_grid_cartesc_fy(je)*1.e-3_rp, ' -HALO- ', atmos_grid_cartesc_fy(ja) *1.e-3_rp
937 
938 
939  log_newline
940  log_info("ATMOS_GRID_CARTESC_output_info",'(1x,A)') 'Vertical Coordinate'
941  log_info_cont('(1x,A)') '|===============================================|'
942  log_info_cont('(1x,A)') '| k z zh dz buffer k |'
943  log_info_cont('(1x,A)') '| [m] [m] [m] factor |'
944 
945  do k = ka, ke+1, -1
946  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
947  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),' |'
948  enddo
949 
950  k = ke
951  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'
952  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),' |'
953 
954  do k = ke-1, ks, -1
955  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
956  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),' |'
957  enddo
958 
959  k = ks-1
960  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'
961  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),' |'
962 
963  do k = ks-2, 1, -1
964  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
965  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),' |'
966  enddo
967 
968  k = 0
969  log_info_cont('(1x,A,F9.2,A,F9.2,I5,A)') '| ',atmos_grid_cartesc_fz(k),' ', atmos_grid_cartesc_fbfz(k),k,' |'
970 
971  log_info_cont('(1x,A)') '|===============================================|'
972 
973 
974  return
975  end subroutine atmos_grid_cartesc_output_info
976 
977 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:342
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:42
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:351
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:67
scale_atmos_grid_cartesc::atmos_grid_cartesc_setup
subroutine, public atmos_grid_cartesc_setup(basename, aggregate)
Setup.
Definition: scale_atmos_grid_cartesC.F90:108
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:65
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:81
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:50
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:78
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:61
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:57
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:83
scale_prc::prc_myrank
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:90
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:63
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:72
scale_atmos_grid_cartesc_index::imaxg
integer, public imaxg
Definition: scale_atmos_grid_cartesC_index.F90:71
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:44
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:80
scale_atmos_grid_cartesc::dx
real(rp), public dx
Definition: scale_atmos_grid_cartesC.F90:38
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:91
scale_atmos_grid_cartesc_index::jmaxg
integer, public jmaxg
Definition: scale_atmos_grid_cartesC_index.F90:72
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:70
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:87
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:74
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:66
scale_atmos_grid_cartesc_index::iag
integer, public iag
Definition: scale_atmos_grid_cartesC_index.F90:73
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:46
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:75
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:44
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:90
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:73
scale_prc_cartesc::prc_2drank
integer, dimension(:,:), allocatable, public prc_2drank
node index in 2D topology
Definition: scale_prc_cartesC.F90:44
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:58
scale_file::file_open
subroutine, public file_open(basename, fid, mode, single, aggregate, rankid, postfix)
Definition: scale_file.F90:487
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:47
scale_atmos_grid_cartesc::atmos_grid_cartesc_output_info
subroutine atmos_grid_cartesc_output_info
Output information.
Definition: scale_atmos_grid_cartesC.F90:919
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:85
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:62
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:51
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:88
scale_atmos_grid_cartesc::dy
real(rp), public dy
Definition: scale_atmos_grid_cartesC.F90:38
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:77
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:182
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:41
scale_atmos_grid_cartesc::atmos_grid_cartesc_name
character(len=7), parameter, public atmos_grid_cartesc_name
Definition: scale_atmos_grid_cartesC.F90:36
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:76
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:42
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:56
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:45
scale_atmos_grid_cartesc::atmos_grid_cartesc_allocate
subroutine, public atmos_grid_cartesc_allocate
Definition: scale_atmos_grid_cartesC.F90:217
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:52
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:71
scale_prc_cartesc::prc_num_x
integer, public prc_num_x
x length of 2D processor topology
Definition: scale_prc_cartesC.F90:41
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:60
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:43
scale_atmos_grid_cartesc::dz
real(rp), public dz
Definition: scale_atmos_grid_cartesC.F90:38
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:40
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:86
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:68
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:56
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:55
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:82