SCALE-RM
scale_atmos_grid_cartesC_index.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  !-----------------------------------------------------------------------------
20  implicit none
21  private
22  !-----------------------------------------------------------------------------
23  !
24  !++ Public procedure
25  !
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public parameters & variables
30  !
31 
32  integer, public, parameter :: zdir = 1
33  integer, public, parameter :: xdir = 2
34  integer, public, parameter :: ydir = 3
35 
36  integer, public :: kmax = -1
37  integer, public :: imax = -1
38  integer, public :: jmax = -1
39 
40  integer, public :: iblock = -1
41  integer, public :: jblock = -1
42 
43  integer, public, parameter :: khalo = 2
44  integer, public :: ihalo = 2
45  integer, public :: jhalo = 2
46 
47  integer, public :: ka
48  integer, public :: ia
49  integer, public :: ja
50 
51  integer, public :: ks
52  integer, public :: ke
53  integer, public :: is
54  integer, public :: ie
55  integer, public :: js
56  integer, public :: je
57 
58  integer, public :: kijmax = -1
59 
60  ! indices considering boundary
61  integer, public :: imaxb
62  integer, public :: jmaxb
63  integer, public :: isb
64  integer, public :: ieb
65  integer, public :: jsb
66  integer, public :: jeb
67  integer, public :: ieh
68  integer, public :: jeh
69 
70  ! global size and offset
71  integer, public :: imaxg = -1
72  integer, public :: jmaxg = -1
73  integer, public :: iag
74  integer, public :: jag
75  integer, public :: iagb
76  integer, public :: jagb
77  integer, public :: is_ing
78  integer, public :: ie_ing
79  integer, public :: js_ing
80  integer, public :: je_ing
81  integer, public :: isga
82  integer, public :: iega
83  integer, public :: jsga
84  integer, public :: jega
85  integer, public :: isgb
86  integer, public :: iegb
87  integer, public :: jsgb
88  integer, public :: jegb
89 
90  integer, public :: i_xyz = 1 ! at (x,y,z)
91  integer, public :: i_xyw = 2 ! at (x,y,w)
92  integer, public :: i_uyw = 3 ! at (u,y,w)
93  integer, public :: i_xvw = 4 ! at (x,v,w)
94  integer, public :: i_uyz = 5 ! at (u,y,z)
95  integer, public :: i_xvz = 6 ! at (x,v,z)
96  integer, public :: i_uvz = 7 ! at (u,v,z)
97 
98  integer, public :: i_xy = 1 ! at (x,y)
99  integer, public :: i_uy = 2 ! at (u,y)
100  integer, public :: i_xv = 3 ! at (x,v)
101  integer, public :: i_uv = 4 ! at (u,v)
102 
103  integer, public :: i_fyz = 1 ! y-z face limiting x-flux
104  integer, public :: i_fxz = 2 ! x-z face limiting y-flux
105  integer, public :: i_fxy = 3 ! x-y face limiting z-flux
106 
107 contains
108 
109  !-----------------------------------------------------------------------------
111  subroutine atmos_grid_cartesc_index_setup( &
112  KMAX, &
113  IMAXG, JMAXG, &
114  IMAX, JMAX, &
115  KHALO, IHALO, JHALO, &
116  IBLOCK, JBLOCK )
117  implicit none
118  integer, intent(in), optional :: KMAX
119  integer, intent(in), optional :: IMAXG, JMAXG
120  integer, intent(in), optional :: IMAX, JMAX
121  integer, intent(in), optional :: KHALO, IHALO, JHALO
122  integer, intent(in), optional :: IBLOCK, JBLOCK
123 
124  call atmos_grid_cartesc_index_setup_main( &
125  kmax, &
126  imaxg, jmaxg, &
127  imax, jmax, &
128  khalo, ihalo, jhalo, &
129  iblock, jblock )
130 
131  return
132  end subroutine atmos_grid_cartesc_index_setup
133 
134  subroutine atmos_grid_cartesc_index_setup_main( &
135  KMAX_in, &
136  IMAXG_in, JMAXG_in, &
137  IMAX_in, JMAX_in, &
138  KHALO_in, IHALO_in, JHALO_in, &
139  IBLOCK_in, JBLOCK_in )
140  use scale_prc, only: &
141  prc_abort, &
142  prc_myrank
143  use scale_prc_cartesc, only: &
144  prc_periodic_x, &
145  prc_periodic_y, &
146  prc_2drank, &
147  prc_num_x, &
148  prc_num_y, &
149  prc_has_w, &
150  prc_has_e, &
151  prc_has_s, &
152  prc_has_n
153  implicit none
154  integer, intent(in), optional :: KMAX_in
155  integer, intent(in), optional :: IMAXG_in, JMAXG_in
156  integer, intent(in), optional :: IMAX_in, JMAX_in
157  integer, intent(in), optional :: KHALO_in, IHALO_in, JHALO_in
158  integer, intent(in), optional :: IBLOCK_in, JBLOCK_in
159 
160  namelist / param_atmos_grid_cartesc_index / &
161  kmax, &
162  imaxg, &
163  jmaxg, &
164  imax, &
165  jmax, &
166  ihalo, &
167  jhalo, &
168  iblock, &
169  jblock
170 
171  integer :: ierr
172  !---------------------------------------------------------------------------
173 
174  if ( present(kmax_in) ) kmax = kmax_in
175  if ( present(imaxg_in) ) imaxg = imaxg_in
176  if ( present(jmaxg_in) ) jmaxg = jmaxg_in
177  if ( present(imax_in) ) imax = imax_in
178  if ( present(jmax_in) ) jmax = jmax_in
179 ! if ( present(KHALO_in) ) KHALO = KHALO_in
180  if ( present(ihalo_in) ) ihalo = ihalo_in
181  if ( present(jhalo_in) ) jhalo = jhalo_in
182  if ( present(iblock_in) ) iblock = iblock_in
183  if ( present(jblock_in) ) jblock = jblock_in
184 
185  log_newline
186  log_info("ATMOS_GRID_CARTESC_index_setup_main",*) 'Setup'
187 
188  !--- read namelist
189  rewind(io_fid_conf)
190  read(io_fid_conf,nml=param_atmos_grid_cartesc_index,iostat=ierr)
191  if( ierr < 0 ) then !--- missing
192  log_info("ATMOS_GRID_CARTESC_index_setup_main",*) 'Not found namelist. Default used.'
193  elseif( ierr > 0 ) then !--- fatal error
194  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'Not appropriate names in namelist PARAM_ATMOS_GRID_CARTESC_INDEX. Check!'
195  call prc_abort
196  endif
197  log_nml(param_atmos_grid_cartesc_index)
198 
199  if ( kmax < 2 ) then
200  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'KMAX must be >= 2! ', kmax
201  call prc_abort
202  end if
203 
204 
205  if ( imaxg * jmaxg < 0 ) then
206  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'Both IMAXG and JMAXG must set! ', imaxg, jmaxg
207  call prc_abort
208  endif
209  if ( imax * jmax < 0 ) then
210  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'Both IMAX and JMAX must set! ', imax, jmax
211  call prc_abort
212  endif
213 
214  if ( imax > 0 .AND. jmax > 0 ) then
215  imaxg = imax * prc_num_x
216  jmaxg = jmax * prc_num_y
217  elseif( imaxg > 0 .AND. jmaxg > 0 ) then
218  imax = (imaxg-1) / prc_num_x + 1
219  jmax = (jmaxg-1) / prc_num_y + 1
220 
221  if ( mod(imaxg,prc_num_x) > 0 ) then
222  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of IMAXG should be divisible by PRC_NUM_X'
223  call prc_abort
224 ! LOG_INFO("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of IMAXG should be divisible by PRC_NUM_X'
225 ! LOG_INFO("ATMOS_GRID_CARTESC_index_setup_main",*) 'Small IMAX is used in ranks(X,*)=', PRC_NUM_X-1
226 ! if ( PRC_2Drank(PRC_myrank,1) == PRC_NUM_X-1 ) then
227 ! IMAX = IMAXG - IMAX * (PRC_NUM_X-1)
228 ! LOG_INFO("ATMOS_GRID_CARTESC_index_setup_main",*) 'Small IMAX is used in this rank. IMAX=', IMAX
229 ! endif
230  endif
231 
232  if ( mod(jmaxg,prc_num_y) > 0 ) then
233  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of JMAXG should be divisible by PRC_NUM_Y'
234  call prc_abort
235 ! LOG_INFO("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of JMAXG should be divisible by PRC_NUM_Y'
236 ! LOG_INFO("ATMOS_GRID_CARTESC_index_setup_main",*) 'Small JMAX is used in ranks(*,Y)=', PRC_NUM_Y-1
237 ! if ( PRC_2Drank(PRC_myrank,2) == PRC_NUM_Y-1 ) then
238 ! JMAX = JMAXG - JMAX * (PRC_NUM_Y-1)
239 ! LOG_INFO("ATMOS_GRID_CARTESC_index_setup_main",*) 'Small JMAX is used in this rank. JMAX=', JMAX
240 ! endif
241  endif
242  else
243  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'IMAXG&JMAXG or IMAX&JMAX must set!'
244  call prc_abort
245  endif
246 
247  if ( imax < ihalo ) then
248  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of grid size IMAX must >= IHALO! ', imax, ihalo
249  call prc_abort
250  endif
251  if ( jmax < jhalo ) then
252  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of grid size JMAX must >= JHALO! ', jmax, jhalo
253  call prc_abort
254  endif
255 
256  ka = kmax + khalo * 2
257  ia = imax + ihalo * 2
258  ja = jmax + jhalo * 2
259 
260  ks = 1 + khalo
261  ke = kmax + khalo
262  is = 1 + ihalo
263  ie = imax + ihalo
264  js = 1 + jhalo
265  je = jmax + jhalo
266 
267  if( iblock == -1 ) iblock = imax
268  if( jblock == -1 ) jblock = jmax
269 
270  kijmax = kmax * imax * jmax
271 
272 
273  !-- Block size must be divisible
274  if ( mod(imax,iblock) > 0 ) then
275  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of grid size IMAX must be divisible by IBLOCK! ', imax, iblock
276  call prc_abort
277  elseif( mod(jmax,jblock) > 0 ) then
278  log_error("ATMOS_GRID_CARTESC_index_setup_main",*) 'number of grid size JMAX must be divisible by JBLOCK! ', jmax, jblock
279  call prc_abort
280  endif
281 
282  ! array size (global domain)
283  iag = imaxg + ihalo * 2
284  jag = jmaxg + jhalo * 2
285 
286  ! horizontal index (global domain)
287  is_ing = ihalo + 1 + prc_2drank(prc_myrank,1) * imax
289  js_ing = jhalo + 1 + prc_2drank(prc_myrank,2) * jmax
291 
292  if ( prc_2drank(prc_myrank,1) == 0 ) then
293  isga = 1
294  else
295  isga = is_ing
296  end if
297  if ( prc_2drank(prc_myrank,1) == prc_num_x - 1 ) then
298  iega = iag
299  else
300  iega = ie_ing
301  end if
302  if ( prc_2drank(prc_myrank,2) == 0 ) then
303  jsga = 1
304  else
305  jsga = js_ing
306  end if
307  if ( prc_2drank(prc_myrank,2) == prc_num_y - 1 ) then
308  jega = jag
309  else
310  jega = je_ing
311  end if
312 
313  if ( prc_periodic_x ) then
314  iagb = imaxg
315  isgb = is_ing - ihalo
316  iegb = ie_ing - ihalo
317  else
318  iagb = iag
319  if ( prc_has_w ) then
320  isgb = is_ing
321  else ! western boundary
322  isgb = is_ing - ihalo ! ISGB = 1
323  end if
324  if ( prc_has_e ) then
325  iegb = ie_ing
326  else ! eastern boundary
327  iegb = ie_ing + ihalo
328  end if
329  end if
330  if ( prc_periodic_y ) then
331  jagb = jmaxg
332  jsgb = js_ing - jhalo
333  jegb = je_ing - jhalo
334  else
335  jagb = jag
336  if ( prc_has_s ) then
337  jsgb = js_ing
338  else ! southern boundary
339  jsgb = js_ing - jhalo ! JSGY = 1
340  end if
341  if ( prc_has_n ) then
342  jegb = je_ing
343  else ! northern boundary
344  jegb = je_ing + jhalo
345  end if
346  end if
347 
348  ! index considering boundary region
349  imaxb = imax
350  jmaxb = jmax
351  isb = is
352  ieb = ie
353  jsb = js
354  jeb = je
355  ieh = ie
356  jeh = je
357 
358  if ( .NOT. prc_has_w ) then
359  imaxb = imaxb + ihalo
360  isb = 1
361  endif
362  if ( .NOT. prc_has_e ) then
363  imaxb = imaxb + ihalo
364  ieb = ia
365  ieh = ie - 1
366  endif
367  if ( .NOT. prc_has_s ) then
368  jmaxb = jmaxb + jhalo
369  jsb = 1
370  endif
371  if ( .NOT. prc_has_n ) then
372  jmaxb = jmaxb + jhalo
373  jeb = ja
374  jeh = je - 1
375  endif
376 
377  log_newline
378  log_info("ATMOS_GRID_CARTESC_index_setup_main",*) 'Atmosphere grid index information '
379 
380  ! global
381  log_info_cont('(1x,3(A,I6))') 'No. of Computational Grid (global) :', &
382  kmax,' x ',imaxg,' x ',jmaxg
383  log_info_cont('(1x,2(A,I6))') 'Global index of local grid (X) :', &
384  is_ing," - ",ie_ing
385  log_info_cont('(1x,2(A,I6))') 'Global index of local grid (Y) :', &
386  js_ing," - ",je_ing
387 
388  ! local
389  log_newline
390  log_info_cont('(1x,3(A,I6))') 'No. of Computational Grid (local) :', &
391  kmax,' x ',imax,' x ',jmax
392  log_info_cont('(1x,3(A,I6))') 'No. of Grid (including HALO, local) :', &
393  ka," x ",ia," x ",ja
394  log_info_cont('(1x,2(A,I6))') 'Local index of inner grid (X) :', &
395  isb," - ",ieb
396  log_info_cont('(1x,2(A,I6))') 'Local index of inner grid (Y) :', &
397  jsb," - ",jeb
398 
399  return
400  end subroutine atmos_grid_cartesc_index_setup_main
401 
integer, public iagb
of computational grids
integer, public jmax
of computational cells: y, local
integer, parameter, public khalo
of halo cells: z
integer, public jsgb
start point of the inner domain: y, global
integer, public imax
of computational cells: x, local
integer, public ia
of whole cells: x, local, with HALO
integer, public iag
of computational grids
integer, public iblock
block size for cache blocking: x
integer, public ja
of whole cells: y, local, with HALO
module process / cartesC
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:55
logical, public prc_has_s
integer, public je_ing
end point of the inner domain: cy, global
integer, public jsga
start point of the full domain: cy, global
integer, public isgb
start point of the inner domain: x, global
logical, public prc_has_n
logical, public prc_has_e
logical, public prc_periodic_y
periodic condition or not (Y)?
integer, public jmaxg
of computational cells: y, global
logical, public prc_periodic_x
periodic condition or not (X)?
subroutine, public atmos_grid_cartesc_index_setup(KMAX, IMAXG, JMAXG, IMAX, JMAX, KHALO, IHALO, JHALO, IBLOCK, JBLOCK)
setup index
integer, public is
start point of inner domain: x, local
integer, public ie
end point of inner domain: x, local
integer, public js_ing
start point of the inner domain: cy, global
integer, public jega
end point of the full domain: cy, global
module atmosphere / grid / cartesC index
integer, public ke
end point of inner domain: z, local
integer, public ie_ing
end point of the inner domain: cx, global
module PROCESS
Definition: scale_prc.F90:11
integer, public je
end point of inner domain: y, local
integer, public iega
end point of the full domain: cx, global
integer, public iegb
end point of the inner domain: x, global
integer, public ieh
end point of inner domain: x, local (half level)
integer, public ks
start point of inner domain: z, local
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:89
integer, public jblock
block size for cache blocking: y
integer, public jegb
end point of the inner domain: y, global
integer, dimension(:,:), allocatable, public prc_2drank
node index in 2D topology
integer, public kmax
of computational cells: z, local
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
integer, public jag
of computational grids
integer, public js
start point of inner domain: y, local
integer, public is_ing
start point of the inner domain: cx, global
integer, public prc_num_y
y length of 2D processor topology
integer, public jagb
of computational grids
integer, public imaxg
of computational cells: x, global
module PRECISION
integer, public ka
of whole cells: z, local, with HALO
integer, public jeh
end point of inner domain: y, local (half level)
module STDIO
Definition: scale_io.F90:10
integer, public isga
start point of the full domain: cx, global
integer, public kijmax
of computational cells: z*x*y
logical, public prc_has_w
integer, public prc_num_x
x length of 2D processor topology