SCALE-RM
scale_atmos_grid_cartesC_real.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  use scale_prof
20  !-----------------------------------------------------------------------------
21  implicit none
22  private
23  !-----------------------------------------------------------------------------
24  !
25  !++ Public procedure
26  !
30 
31  !-----------------------------------------------------------------------------
32  !
33  !++ Public parameters & variables
34  !
37 
38  real(RP), public, allocatable :: atmos_grid_cartesc_real_cz (:,:,:)
39  real(RP), public, allocatable :: atmos_grid_cartesc_real_czuy(:,:,:)
40  real(RP), public, allocatable :: atmos_grid_cartesc_real_czxv(:,:,:)
41  real(RP), public, allocatable :: atmos_grid_cartesc_real_czuv(:,:,:)
42  real(RP), public, allocatable :: atmos_grid_cartesc_real_fz (:,:,:)
43  real(RP), public, allocatable :: atmos_grid_cartesc_real_fzuy(:,:,:)
44  real(RP), public, allocatable :: atmos_grid_cartesc_real_fzxv(:,:,:)
45  real(RP), public, allocatable :: atmos_grid_cartesc_real_fzuv(:,:,:)
46 
47  real(RP), public, allocatable :: atmos_grid_cartesc_real_lon (:,:)
48  real(RP), public, allocatable :: atmos_grid_cartesc_real_lonuy(:,:)
49  real(RP), public, allocatable :: atmos_grid_cartesc_real_lonxv(:,:)
50  real(RP), public, allocatable :: atmos_grid_cartesc_real_lonuv(:,:)
51  real(RP), public, allocatable :: atmos_grid_cartesc_real_lat (:,:)
52  real(RP), public, allocatable :: atmos_grid_cartesc_real_latuy(:,:)
53  real(RP), public, allocatable :: atmos_grid_cartesc_real_latxv(:,:)
54  real(RP), public, allocatable :: atmos_grid_cartesc_real_latuv(:,:)
55  real(RP), public, allocatable :: atmos_grid_cartesc_real_dlon (:,:)
56  real(RP), public, allocatable :: atmos_grid_cartesc_real_dlat (:,:)
57 
58  real(RP), public, allocatable :: atmos_grid_cartesc_real_z1 (:,:)
61 
62  real(RP), public, allocatable :: atmos_grid_cartesc_real_phi (:,:,:)
63 
64  real(RP), public, allocatable :: atmos_grid_cartesc_real_area (:,:)
65  real(RP), public, allocatable :: atmos_grid_cartesc_real_areazuy_x(:,:,:)
66  real(RP), public, allocatable :: atmos_grid_cartesc_real_areazxv_y(:,:,:)
67  real(RP), public, allocatable :: atmos_grid_cartesc_real_areawuy_x(:,:,:)
68  real(RP), public, allocatable :: atmos_grid_cartesc_real_areawxv_y(:,:,:)
69  real(RP), public, allocatable :: atmos_grid_cartesc_real_areauy (:,:)
70  real(RP), public, allocatable :: atmos_grid_cartesc_real_areazxy_x(:,:,:)
71  real(RP), public, allocatable :: atmos_grid_cartesc_real_areazuv_y(:,:,:)
72  real(RP), public, allocatable :: atmos_grid_cartesc_real_areaxv (:,:)
73  real(RP), public, allocatable :: atmos_grid_cartesc_real_areazuv_x(:,:,:)
74  real(RP), public, allocatable :: atmos_grid_cartesc_real_areazxy_y(:,:,:)
75 
76  real(RP), public :: atmos_grid_cartesc_real_totarea
79 
80  real(RP), public, allocatable :: atmos_grid_cartesc_real_vol (:,:,:)
81  real(RP), public, allocatable :: atmos_grid_cartesc_real_volwxy(:,:,:)
82  real(RP), public, allocatable :: atmos_grid_cartesc_real_volzuy(:,:,:)
83  real(RP), public, allocatable :: atmos_grid_cartesc_real_volzxv(:,:,:)
84  real(RP), public :: atmos_grid_cartesc_real_totvol
88 
89  real(RP), public, allocatable :: atmos_grid_cartesc_real_domain_catalogue(:,:,:)
90 
91  !-----------------------------------------------------------------------------
92  !
93  !++ Private procedure
94  !
95  private :: atmos_grid_cartesc_real_calc_latlon
96  private :: atmos_grid_cartesc_real_calc_z
97 
98  !-----------------------------------------------------------------------------
99  !
100  !++ Private parameters & variables
101  !
102  !-----------------------------------------------------------------------------
103 contains
104  !-----------------------------------------------------------------------------
107  use scale_prc, only: &
108  prc_nprocs, &
109  prc_abort
110  use scale_atmos_grid_cartesc, only: &
115  use scale_topography, only: &
116  topo_exist
117  use scale_mapprojection, only: &
119  use scale_interp_vert, only: &
121  implicit none
122 
123  character(len=H_LONG) :: DOMAIN_CATALOGUE_FNAME = 'latlon_domain_catalogue.txt'
124  logical :: DOMAIN_CATALOGUE_OUTPUT = .false.
125 
126  namelist / param_domain_catalogue / &
127  domain_catalogue_fname, &
128  domain_catalogue_output
129 
130  integer :: ierr
131  !---------------------------------------------------------------------------
132 
133  log_newline
134  log_info("ATMOS_GRID_CARTESC_REAL_setup",*) 'Setup'
135 
136  !--- read namelist
137  rewind(io_fid_conf)
138  read(io_fid_conf,nml=param_domain_catalogue,iostat=ierr)
139  if( ierr < 0 ) then !--- missing
140  log_info("ATMOS_GRID_CARTESC_REAL_setup",*) 'Not found namelist. Default used.'
141  elseif( ierr > 0 ) then !--- fatal error
142  log_error("ATMOS_GRID_CARTESC_REAL_setup",*) 'Not appropriate names in namelist PARAM_DOMAIN_CATALOGUE. Check!'
143  call prc_abort
144  endif
145  log_nml(param_domain_catalogue)
146 
147  allocate( atmos_grid_cartesc_real_lon( ia, ja) )
148  allocate( atmos_grid_cartesc_real_lat( ia, ja) )
149  allocate( atmos_grid_cartesc_real_lonuy(0:ia, ja) )
150  allocate( atmos_grid_cartesc_real_lonxv( ia,0:ja) )
151  allocate( atmos_grid_cartesc_real_lonuv(0:ia,0:ja) )
152  allocate( atmos_grid_cartesc_real_latuy(0:ia, ja) )
153  allocate( atmos_grid_cartesc_real_latxv( ia,0:ja) )
154  allocate( atmos_grid_cartesc_real_latuv(0:ia,0:ja) )
155  allocate( atmos_grid_cartesc_real_dlon( ia, ja) )
156  allocate( atmos_grid_cartesc_real_dlat( ia, ja) )
157 
158  allocate( atmos_grid_cartesc_real_cz( ka,ia,ja) )
159  allocate( atmos_grid_cartesc_real_czuy( ka,ia,ja) )
160  allocate( atmos_grid_cartesc_real_czxv( ka,ia,ja) )
161  allocate( atmos_grid_cartesc_real_czuv( ka,ia,ja) )
162  allocate( atmos_grid_cartesc_real_fz(0:ka,ia,ja) )
163  allocate( atmos_grid_cartesc_real_fzuy(0:ka,ia,ja) )
164  allocate( atmos_grid_cartesc_real_fzxv(0:ka,ia,ja) )
165  allocate( atmos_grid_cartesc_real_fzuv(0:ka,ia,ja) )
166  allocate( atmos_grid_cartesc_real_z1( ia,ja) )
167  allocate( atmos_grid_cartesc_real_phi( ka,ia,ja) )
168 
169  allocate( atmos_grid_cartesc_real_area( ia,ja) )
174  allocate( atmos_grid_cartesc_real_areauy( ia,ja) )
177  allocate( atmos_grid_cartesc_real_areaxv( ia,ja) )
180 
181  allocate( atmos_grid_cartesc_real_vol( ka,ia,ja) )
182  allocate( atmos_grid_cartesc_real_volwxy(0:ka,ia,ja) )
183  allocate( atmos_grid_cartesc_real_volzuy( ka,ia,ja) )
184  allocate( atmos_grid_cartesc_real_volzxv( ka,ia,ja) )
185 
187 
188  ! setup map projection
190 
191  ! calc longitude & latitude
192  call atmos_grid_cartesc_real_calc_latlon( domain_catalogue_fname, domain_catalogue_output )
193 
194  ! calc real height
195  call atmos_grid_cartesc_real_calc_z
196 
197  call interp_vert_setcoef( ka, ks, ke, & ! [IN]
198  ia, 1, ia, & ! [IN]
199  ja, 1, ja, & ! [IN]
200  topo_exist, & ! [IN]
201  atmos_grid_cartesc_cz(:), & ! [IN]
202  atmos_grid_cartesc_fz(:), & ! [IN]
203  atmos_grid_cartesc_real_cz(:,:,:), & ! [IN]
204  atmos_grid_cartesc_real_fz(:,:,:) ) ! [IN]
205 
206  return
207  end subroutine atmos_grid_cartesc_real_setup
208 
209  !-----------------------------------------------------------------------------
212  use scale_file_cartesc, only: &
214  use scale_topography, only: &
215  topo_zsfc
216  use scale_landuse, only: &
218  implicit none
219  !---------------------------------------------------------------------------
220 
221  ! calc real height
222  call atmos_grid_cartesc_real_calc_z
223 
224  ! set latlon and z to fileio module
228  topo_zsfc, landuse_frac_land, & ! [IN]
234 
235  return
236  end subroutine atmos_grid_cartesc_real_update_z
237 
238  !-----------------------------------------------------------------------------
240  subroutine atmos_grid_cartesc_real_calc_latlon( &
241  catalogue_fname, &
242  catalogue_output )
243  use scale_prc, only: &
244  prc_abort, &
245  prc_nprocs, &
247  use scale_const, only: &
248  pi => const_pi, &
249  d2r => const_d2r
250  use scale_atmos_grid_cartesc, only: &
255  use scale_comm_cartesc, only: &
256  comm_gather, &
257  comm_bcast
258  use scale_mapprojection, only: &
261  mapprojection_xy2lonlat
262  implicit none
263 
264  character(len=*), intent(in) :: catalogue_fname
265  logical, intent(in) :: catalogue_output
266 
267  integer, parameter :: I_MIN = 1
268  integer, parameter :: I_MAX = 2
269  integer, parameter :: I_LON = 1
270  integer, parameter :: I_LAT = 2
271 
272  real(RP) :: mine (2,2)
273  real(RP) :: whole(2,2,prc_nprocs)
274 
275  integer :: i, j
276  integer :: fid, ierr
277  !---------------------------------------------------------------------------
278 
281 
282  log_newline
283  log_info("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'Base position in the global domain (lat,lon)'
285 
286  !$omp parallel do collapse(2)
287  do j = 1, ja
288  do i = 1, ia
290  enddo
291  enddo
292 
293  !$omp parallel do collapse(2)
294  do j = 1, ja
295  do i = 0, ia
297  enddo
298  enddo
299 
300  !$omp parallel do collapse(2)
301  do j = 0, ja
302  do i = 1, ia
304  enddo
305  enddo
306 
307  !$omp parallel do collapse(2)
308  do j = 0, ja
309  do i = 0, ia
311  enddo
312  enddo
313 
314  atmos_grid_cartesc_real_dlon(:,:) = 0.0_rp
315  atmos_grid_cartesc_real_dlat(:,:) = 0.0_rp
316  !$omp parallel do
317  do j = js, je
318  do i = is, ie
322 
323  if ( atmos_grid_cartesc_real_dlon(i,j) == 0.0_rp &
324  .OR. atmos_grid_cartesc_real_dlat(i,j) == 0.0_rp ) then
325  log_error("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'Invalid grid distance in lat-lon! i,j=', i,j
326  log_error_cont(*) 'Lon(i-1),Lon(i),dlon=', atmos_grid_cartesc_real_lonuy(i-1,j)/d2r,atmos_grid_cartesc_real_lonuy(i,j)/d2r,atmos_grid_cartesc_real_dlon(i,j)/d2r
327  log_error_cont(*) 'Lat(j-1),Lat(j),dlat=', atmos_grid_cartesc_real_latxv(i,j-1)/d2r,atmos_grid_cartesc_real_latxv(i,j)/d2r,atmos_grid_cartesc_real_dlat(i,j)/d2r
328  call prc_abort
329  endif
330  enddo
331  enddo
332 
333  log_newline
334  log_info("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'Position on the earth (Local)'
335  log_info_cont('(1x,A,F10.5,A,F9.5,A,A,F10.5,A,F9.5,A)') &
338 
339  log_info_cont('(1x,A)') ' | |'
340  log_info_cont('(1x,A,F10.5,A,F9.5,A,A,F10.5,A,F9.5,A)') &
343 
344  mine(i_min,i_lon) = minval(atmos_grid_cartesc_real_lonuv(:,:)) / d2r
345  mine(i_max,i_lon) = maxval(atmos_grid_cartesc_real_lonuv(:,:)) / d2r
346  mine(i_min,i_lat) = minval(atmos_grid_cartesc_real_latuv(:,:)) / d2r
347  mine(i_max,i_lat) = maxval(atmos_grid_cartesc_real_latuv(:,:)) / d2r
348 
349  call comm_gather( whole(:,:,:), mine(:,:), 2, 2 ) ! everytime do for online nesting
350 
351  if ( prc_ismaster ) then
352  if ( catalogue_output ) then
353 
354  fid = io_get_available_fid()
355  open( fid, &
356  file = trim(catalogue_fname), &
357  form = 'formatted', &
358  status = 'replace', &
359  iostat = ierr )
360 
361  if ( ierr /= 0 ) then
362  log_error("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'cannot create latlon-catalogue file!'
363  call prc_abort
364  endif
365 
366  do i = 1, prc_nprocs ! for offline nesting
367  write(fid,'(I8,8F32.24)',iostat=ierr) i, whole(i_min,i_lon,i), whole(i_max,i_lon,i), & ! LON: MIN, MAX
368  whole(i_min,i_lat,i), whole(i_max,i_lat,i) ! LAT: MIN, MAX
369  if ( ierr /= 0 ) exit
370  enddo
371 
372  close(fid)
373 
374  endif
375 
376  do i = 1, prc_nprocs ! for online nesting
377  atmos_grid_cartesc_real_domain_catalogue(i,i_min,i_lon) = whole(i_min,i_lon,i)
378  atmos_grid_cartesc_real_domain_catalogue(i,i_max,i_lon) = whole(i_max,i_lon,i)
379  atmos_grid_cartesc_real_domain_catalogue(i,i_min,i_lat) = whole(i_min,i_lat,i)
380  atmos_grid_cartesc_real_domain_catalogue(i,i_max,i_lat) = whole(i_max,i_lat,i)
381  enddo
382  endif
383 
384  call comm_bcast( atmos_grid_cartesc_real_domain_catalogue(:,:,:), prc_nprocs, 2, 2 )
385 
386  return
387  end subroutine atmos_grid_cartesc_real_calc_latlon
388 
389  !-----------------------------------------------------------------------------
391  subroutine atmos_grid_cartesc_real_calc_z
392  use scale_const, only: &
393  grav => const_grav
394  use scale_atmos_grid_cartesc, only: &
399  use scale_topography, only: &
400  zsfc => topo_zsfc
401  implicit none
402 
403  real(RP) :: Htop
404  real(RP) :: Zs
405  real(RP) :: DFZ
406 
407  integer :: k, i, j
408  !---------------------------------------------------------------------------
409 
411 
412  do j = 1, ja
413  do i = 1, ia
414  zs = zsfc(i,j)
415  do k = 1, ka
416  atmos_grid_cartesc_real_cz(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
417  enddo
418  enddo
419  enddo
420 
421  do j = 1, ja
422  do i = 1, ia-1
423  zs = ( zsfc(i,j) + zsfc(i+1,j) ) * 0.5_rp
424  do k = 1, ka
425  atmos_grid_cartesc_real_czuy(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
426  enddo
427  enddo
428  enddo
429  do j = 1, ja
430  zs = zsfc(ia,j)
431  do k = 1, ka
432  atmos_grid_cartesc_real_czuy(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
433  enddo
434  enddo
435 
436  do j = 1, ja-1
437  do i = 1, ia
438  zs = ( zsfc(i,j) + zsfc(i,j+1) ) * 0.5_rp
439  do k = 1, ka
440  atmos_grid_cartesc_real_czxv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
441  enddo
442  enddo
443  enddo
444  do i = 1, ia
445  zs = zsfc(i,ja)
446  do k = 1, ka
447  atmos_grid_cartesc_real_czxv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
448  enddo
449  enddo
450 
451  do j = 1, ja-1
452  do i = 1, ia-1
453  zs = ( zsfc(i,j) + zsfc(i+1,j) + zsfc(i,j+1) + zsfc(i+1,j+1) ) * 0.25_rp
454  do k = 1, ka
455  atmos_grid_cartesc_real_czuv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
456  enddo
457  enddo
458  enddo
459  do j = 1, ja-1
460  zs = ( zsfc(ia,j) + zsfc(ia,j+1) ) * 0.5_rp
461  do k = 1, ka
462  atmos_grid_cartesc_real_czuv(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
463  enddo
464  enddo
465  do i = 1, ia-1
466  zs = ( zsfc(i,ja) + zsfc(i+1,ja) ) * 0.5_rp
467  do k = 1, ka
468  atmos_grid_cartesc_real_czuv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
469  enddo
470  enddo
471  zs = zsfc(ia,ja)
472  do k = 1, ka
473  atmos_grid_cartesc_real_czuv(k,ia,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
474  enddo
475 
476 
477  do j = 1, ja
478  do i = 1, ia
479  zs = zsfc(i,j)
480  do k = 0, ka
481  atmos_grid_cartesc_real_fz(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
482  end do
483  end do
484  end do
485 
486  do j = 1, ja
487  do i = 1, ia-1
488  zs = ( zsfc(i,j) + zsfc(i+1,j) ) * 0.5_rp
489  do k = 0, ka
490  atmos_grid_cartesc_real_fzuy(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
491  end do
492  end do
493  end do
494  do j = 1, ja
495  zs = zsfc(ia,j)
496  do k = 0, ka
497  atmos_grid_cartesc_real_fzuy(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
498  end do
499  end do
500 
501  do j = 1, ja-1
502  do i = 1, ia
503  zs = ( zsfc(i,j) + zsfc(i,j+1) ) * 0.5_rp
504  do k = 0, ka
505  atmos_grid_cartesc_real_fzxv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
506  enddo
507  enddo
508  enddo
509  do i = 1, ia
510  zs = zsfc(i,ja)
511  do k = 0, ka
512  atmos_grid_cartesc_real_fzxv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
513  enddo
514  enddo
515 
516  do j = 1, ja-1
517  do i = 1, ia-1
518  zs = ( zsfc(i,j) + zsfc(i+1,j) + zsfc(i,j+1) + zsfc(i+1,j+1) ) * 0.25_rp
519  do k = 0, ka
520  atmos_grid_cartesc_real_fzuv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
521  enddo
522  enddo
523  enddo
524  do j = 1, ja-1
525  zs = ( zsfc(ia,j) + zsfc(ia,j+1) ) * 0.5_rp
526  do k = 0, ka
527  atmos_grid_cartesc_real_fzuv(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
528  enddo
529  enddo
530  do i = 1, ia-1
531  zs = ( zsfc(i,ja) + zsfc(i+1,ja) ) * 0.5_rp
532  do k = 0, ka
533  atmos_grid_cartesc_real_fzuv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
534  enddo
535  enddo
536  zs = zsfc(ia,ja)
537  do k = 0, ka
538  atmos_grid_cartesc_real_fzuv(k,ia,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
539  enddo
540 
541 
543 
545 
548  do j = js, je
549  do i = is, ie
550  do k = ks, ke
554  enddo
555  enddo
556  enddo
557 
558  log_newline
559  log_info("ATMOS_GRID_CARTESC_REAL_calc_Z",*) 'Minimum & maximum aspect ratio'
561 
562  return
563  end subroutine atmos_grid_cartesc_real_calc_z
564 
565  !-----------------------------------------------------------------------------
568  MAPF )
574  use scale_comm_cartesc, only: &
575  comm_vars8, &
576  comm_wait
577  use scale_file_cartesc, only: &
579  use scale_topography, only: &
580  topo_zsfc
581  use scale_landuse, only: &
583  implicit none
584 
585  real(RP), intent(in) :: MAPF(ia,ja,2,4)
586 
587  real(RP) :: AREAUV(ia,ja)
588 
589  integer :: k, i, j
590  !---------------------------------------------------------------------------
591 
592  atmos_grid_cartesc_real_area(:,:) = 0.0_rp
593  atmos_grid_cartesc_real_areazuy_x(:,:,:) = 0.0_rp
594  atmos_grid_cartesc_real_areazxv_y(:,:,:) = 0.0_rp
595  atmos_grid_cartesc_real_areawuy_x(:,:,:) = 0.0_rp
596  atmos_grid_cartesc_real_areawxv_y(:,:,:) = 0.0_rp
597  atmos_grid_cartesc_real_areauy(:,:) = 0.0_rp
598  atmos_grid_cartesc_real_areazxy_x(:,:,:) = 0.0_rp
599  atmos_grid_cartesc_real_areazuv_y(:,:,:) = 0.0_rp
600  atmos_grid_cartesc_real_areaxv(:,:) = 0.0_rp
601  atmos_grid_cartesc_real_areazuv_y(:,:,:) = 0.0_rp
602  atmos_grid_cartesc_real_areazxy_y(:,:,:) = 0.0_rp
603 
607 
608  atmos_grid_cartesc_real_vol(:,:,:) = 0.0_rp
609  atmos_grid_cartesc_real_volwxy(:,:,:) = 0.0_rp
610  atmos_grid_cartesc_real_volzuy(:,:,:) = 0.0_rp
611  atmos_grid_cartesc_real_volzxv(:,:,:) = 0.0_rp
616 
617  do j = js, je
618  do i = is, ie
619  atmos_grid_cartesc_real_area(i,j) = atmos_grid_cartesc_cdx(i) * atmos_grid_cartesc_cdy(j) / ( mapf(i,j,1,i_xy) * mapf(i,j,2,i_xy) )
620  atmos_grid_cartesc_real_areauy(i,j) = atmos_grid_cartesc_fdx(i) * atmos_grid_cartesc_cdy(j) / ( mapf(i,j,1,i_uy) * mapf(i,j,2,i_uy) )
621  atmos_grid_cartesc_real_areaxv(i,j) = atmos_grid_cartesc_cdx(i) * atmos_grid_cartesc_fdy(j) / ( mapf(i,j,1,i_xv) * mapf(i,j,2,i_xv) )
622  areauv(i,j) = atmos_grid_cartesc_fdx(i) * atmos_grid_cartesc_fdy(j) / ( mapf(i,j,1,i_uv) * mapf(i,j,2,i_uv) )
623  end do
624  end do
625 
626  call comm_vars8( atmos_grid_cartesc_real_area(:,:), 1 )
627  call comm_vars8( atmos_grid_cartesc_real_areauy(:,:), 2 )
628  call comm_vars8( atmos_grid_cartesc_real_areaxv(:,:), 3 )
629  call comm_vars8( areauv(:,:), 4 )
630 
631  do j = js, je
632  do i = is, ie
636  enddo
637  enddo
638 
639  do j = 1, ja
640  do i = 1, ia
641  do k = ks, ke
644  end do
645  do k = ks-1, ke
648  end do
649  do k = ks, ke
654  end do
655  end do
656  end do
657 
658 
659  call comm_wait( atmos_grid_cartesc_real_area(:,:), 1 )
660  call comm_wait( atmos_grid_cartesc_real_areauy(:,:), 2 )
661  call comm_wait( atmos_grid_cartesc_real_areaxv(:,:), 3 )
662  call comm_wait( areauv(:,:), 4 )
663 
664 
665  do j = 1, ja
666  do i = 1, ia
667  do k = ks, ke
671  end do
672  do k = ks-1, ke
674  end do
675  end do
676  end do
677  do j = js, je
678  do i = is, ie
679  do k = ks, ke
684  enddo
685  enddo
686  enddo
687 
688 
689  ! set latlon and z to fileio module
693  topo_zsfc, landuse_frac_land, & ! [IN]
699 
700  return
702 
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdy
y-length of control volume [m]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawuy_x
virtical area (wuy, normal x) [m2]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_phi
geopotential [m2/s2] (cell center)
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdx
x-length of control volume [m]
subroutine, public mapprojection_setup(DOMAIN_CENTER_X, DOMAIN_CENTER_Y)
Setup.
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuv
longitude at staggered point (uv) [rad,0-2pi]
real(rp), public atmos_grid_cartesc_real_basepoint_lon
position of base point in real world [rad,0-2pi]
integer, public ia
of whole cells: x, local, with HALO
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_domain_catalogue
domain latlon catalogue [rad]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areaxv
horizontal area ( xv, normal z) [m2]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areauy
horizontal area ( uy, normal z) [m2]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzuy
geopotential height [m] (wuy)
real(rp), public atmos_grid_cartesc_real_totvolzxv
total volume (zxv, local) [m3]
module INTERPOLATION vertical
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawxv_y
virtical area (wxv, normal y) [m2]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzuv
geopotential height [m] (wuv)
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
integer, public ja
of whole cells: y, local, with HALO
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:55
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:32
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzxv
control volume (zxv) [m3]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fz
face coordinate [m]: z, local
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuy_x
virtical area (zuy, normal x) [m2]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdy
y-length of grid(j+1) to grid(j) [m]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
longitude [rad,0-2pi]
subroutine, public atmos_grid_cartesc_real_setup
Setup.
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czxv
geopotential height [m] (zxv)
integer, public prc_nprocs
myrank in local communicator
Definition: scale_prc.F90:88
real(rp), public atmos_grid_cartesc_real_aspect_min
minimum aspect ratio of the grid cell
module COMMUNICATION
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_z1
Height of the lowermost grid from surface (cell center) [m].
real(rp), public atmos_grid_cartesc_real_totvolzuy
total volume (zuy, local) [m3]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cy
center coordinate [m]: y, local
integer, public is
start point of inner domain: x, local
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czuy
geopotential height [m] (zuy)
real(rp), public atmos_grid_cartesc_real_totareauy
total area (uy, local) [m2]
integer, public ie
end point of inner domain: x, local
module LANDUSE
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_dlon
delta longitude
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuy
latitude at staggered point (uy) [rad,-pi,pi]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdx
x-length of grid(i+1) to grid(i) [m]
module atmosphere / grid / cartesC index
integer, public ke
end point of inner domain: z, local
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volwxy
control volume (wxy) [m3]
integer function, public io_get_available_fid()
search & get available file ID
Definition: scale_io.F90:313
module PROCESS
Definition: scale_prc.F90:11
subroutine, public file_cartesc_set_coordinates_atmos(CZ, FZ, LON, LONUY, LONXV, LONUV, LAT, LATUY, LATXV, LATUV, TOPO, LSMASK, AREA, AREAZUY_X, AREAZXV_Y, AREAWUY_X, AREAWXV_Y, AREAUY, AREAZXY_X, AREAZUV_Y, AREAXV, AREAZUV_X, AREAZXY_Y, VOL, VOLWXY, VOLZUY, VOLZXV)
set latlon and z for atmosphere
real(rp), public atmos_grid_cartesc_real_basepoint_lat
position of base point in real world [rad,-pi,pi]
integer, public je
end point of inner domain: y, local
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cx
center coordinate [m]: x, local
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:46
subroutine, public atmos_grid_cartesc_real_update_z
Re-setup with updated topography.
module atmosphere / grid / cartesC
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonxv
longitude at staggered point (xv) [rad,0-2pi]
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuy
longitude at staggered point (uy) [rad,0-2pi]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_y
virtical area (zxy, normal y) [m2]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czuv
geopotential height [m] (zuv)
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_dlat
delta latitude
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fy
face coordinate [m]: y, local
integer, public js
start point of inner domain: y, local
real(rp), public atmos_grid_cartesc_real_totvolwxy
total volume (wxy, local) [m3]
real(rp), public mapprojection_basepoint_lon
logical, public topo_exist
topography exists?
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
module profiler
Definition: scale_prof.F90:11
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_x
virtical area (zxy, normal x) [m2]
logical, public prc_ismaster
master process in local communicator?
Definition: scale_prc.F90:90
module Atmosphere GRID CartesC Real(real space)
module Map projection
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
horizontal area ( xy, normal z) [m2]
module PRECISION
module file / cartesianC
real(rp), public atmos_grid_cartesc_real_totareaxv
total area (xv, local) [m2]
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fx
face coordinate [m]: x, local
integer, public ka
of whole cells: z, local, with HALO
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzxv
geopotential height [m] (wxv)
module TOPOGRAPHY
real(rp), public const_pi
pi
Definition: scale_const.F90:31
subroutine, public interp_vert_setcoef(KA, KS, KE, IA, IS, IE, JA, JS, JE, TOPO_exist, Xi, Xih, Z, Zh)
Setup.
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuv
latitude at staggered point (uv) [rad,-pi,pi]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latxv
latitude at staggered point (xv) [rad,-pi,pi]
real(rp), public atmos_grid_cartesc_domain_center_x
center position of global domain [m]: x
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_x
virtical area (zuv, normal x) [m2]
module STDIO
Definition: scale_io.F90:10
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_y
virtical area (zuv, normal y) [m2]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
subroutine, public atmos_grid_cartesc_real_calc_areavol(MAPF)
Calc control area/volume.
real(rp), public atmos_grid_cartesc_domain_center_y
center position of global domain [m]: y
real(rp), public mapprojection_basepoint_lat
real(rp), public atmos_grid_cartesc_real_aspect_max
maximum aspect ratio of the grid cell
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzuy
control volume (zuy) [m3]
real(rp), dimension(:,:), allocatable, public landuse_frac_land
land fraction
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxv_y
virtical area (zxv, normal y) [m2]
real(rp), public atmos_grid_cartesc_real_totarea
total area (xy, local) [m2]