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  real(rp), public, allocatable :: atmos_grid_cartesc_real_f2h (:,:,:,:)
47 
48  real(rp), public, allocatable :: atmos_grid_cartesc_real_lon (:,:)
49  real(rp), public, allocatable :: atmos_grid_cartesc_real_lonuy(:,:)
50  real(rp), public, allocatable :: atmos_grid_cartesc_real_lonxv(:,:)
51  real(rp), public, allocatable :: atmos_grid_cartesc_real_lonuv(:,:)
52  real(rp), public, allocatable :: atmos_grid_cartesc_real_lat (:,:)
53  real(rp), public, allocatable :: atmos_grid_cartesc_real_latuy(:,:)
54  real(rp), public, allocatable :: atmos_grid_cartesc_real_latxv(:,:)
55  real(rp), public, allocatable :: atmos_grid_cartesc_real_latuv(:,:)
56  real(rp), public, allocatable :: atmos_grid_cartesc_real_dlon (:,:)
57  real(rp), public, allocatable :: atmos_grid_cartesc_real_dlat (:,:)
58 
59  real(rp), public, allocatable :: atmos_grid_cartesc_real_z1 (:,:)
62 
63  real(rp), public, allocatable :: atmos_grid_cartesc_real_phi (:,:,:)
64 
65  real(rp), public, allocatable :: atmos_grid_cartesc_real_area (:,:)
66  real(rp), public, allocatable :: atmos_grid_cartesc_real_areazuy_x(:,:,:)
67  real(rp), public, allocatable :: atmos_grid_cartesc_real_areazxv_y(:,:,:)
68  real(rp), public, allocatable :: atmos_grid_cartesc_real_areawuy_x(:,:,:)
69  real(rp), public, allocatable :: atmos_grid_cartesc_real_areawxv_y(:,:,:)
70  real(rp), public, allocatable :: atmos_grid_cartesc_real_areauy (:,:)
71  real(rp), public, allocatable :: atmos_grid_cartesc_real_areazxy_x(:,:,:)
72  real(rp), public, allocatable :: atmos_grid_cartesc_real_areazuv_y(:,:,:)
73  real(rp), public, allocatable :: atmos_grid_cartesc_real_areaxv (:,:)
74  real(rp), public, allocatable :: atmos_grid_cartesc_real_areazuv_x(:,:,:)
75  real(rp), public, allocatable :: atmos_grid_cartesc_real_areazxy_y(:,:,:)
76 
80  real(rp), public, allocatable :: atmos_grid_cartesc_real_totareazuy_x(:)
81  real(rp), public, allocatable :: atmos_grid_cartesc_real_totareazxv_y(:)
82 
83  real(rp), public, allocatable :: atmos_grid_cartesc_real_vol (:,:,:)
84  real(rp), public, allocatable :: atmos_grid_cartesc_real_volwxy(:,:,:)
85  real(rp), public, allocatable :: atmos_grid_cartesc_real_volzuy(:,:,:)
86  real(rp), public, allocatable :: atmos_grid_cartesc_real_volzxv(:,:,:)
91 
92  real(rp), public, allocatable :: atmos_grid_cartesc_real_domain_catalogue(:,:,:)
93 
94  !-----------------------------------------------------------------------------
95  !
96  !++ Private procedure
97  !
98  private :: atmos_grid_cartesc_real_calc_latlon
99 
100  !-----------------------------------------------------------------------------
101  !
102  !++ Private parameters & variables
103  !
104  !-----------------------------------------------------------------------------
105 contains
106  !-----------------------------------------------------------------------------
109  use scale_prc, only: &
110  prc_nprocs, &
111  prc_abort
112  use scale_atmos_grid_cartesc, only: &
117  use scale_topography, only: &
119  use scale_mapprojection, only: &
121  use scale_interp_vert, only: &
123  implicit none
124 
125  character(len=H_LONG) :: domain_catalogue_fname = 'latlon_domain_catalogue.txt'
126  logical :: domain_catalogue_output = .false.
127 
128  namelist / param_domain_catalogue / &
129  domain_catalogue_fname, &
130  domain_catalogue_output
131 
132  integer :: ierr
133  !---------------------------------------------------------------------------
134 
135  log_newline
136  log_info("ATMOS_GRID_CARTESC_REAL_setup",*) 'Setup'
137 
138  !--- read namelist
139  rewind(io_fid_conf)
140  read(io_fid_conf,nml=param_domain_catalogue,iostat=ierr)
141  if( ierr < 0 ) then !--- missing
142  log_info("ATMOS_GRID_CARTESC_REAL_setup",*) 'Not found namelist. Default used.'
143  elseif( ierr > 0 ) then !--- fatal error
144  log_error("ATMOS_GRID_CARTESC_REAL_setup",*) 'Not appropriate names in namelist PARAM_DOMAIN_CATALOGUE. Check!'
145  call prc_abort
146  endif
147  log_nml(param_domain_catalogue)
148 
149  allocate( atmos_grid_cartesc_real_lon( ia, ja) )
150  allocate( atmos_grid_cartesc_real_lat( ia, ja) )
151  allocate( atmos_grid_cartesc_real_lonuy(0:ia, ja) )
152  allocate( atmos_grid_cartesc_real_lonxv( ia,0:ja) )
153  allocate( atmos_grid_cartesc_real_lonuv(0:ia,0:ja) )
154  allocate( atmos_grid_cartesc_real_latuy(0:ia, ja) )
155  allocate( atmos_grid_cartesc_real_latxv( ia,0:ja) )
156  allocate( atmos_grid_cartesc_real_latuv(0:ia,0:ja) )
157  allocate( atmos_grid_cartesc_real_dlon( ia, ja) )
158  allocate( atmos_grid_cartesc_real_dlat( ia, ja) )
159 
160  allocate( atmos_grid_cartesc_real_cz( ka,ia,ja) )
161  allocate( atmos_grid_cartesc_real_czuy( ka,ia,ja) )
162  allocate( atmos_grid_cartesc_real_czxv( ka,ia,ja) )
163  allocate( atmos_grid_cartesc_real_czuv( ka,ia,ja) )
164  allocate( atmos_grid_cartesc_real_fz(0:ka,ia,ja) )
165  allocate( atmos_grid_cartesc_real_fzuy(0:ka,ia,ja) )
166  allocate( atmos_grid_cartesc_real_fzxv(0:ka,ia,ja) )
167  allocate( atmos_grid_cartesc_real_fzuv(0:ka,ia,ja) )
168  allocate( atmos_grid_cartesc_real_f2h(ka,2,ia,ja) )
169  allocate( atmos_grid_cartesc_real_z1( ia,ja) )
170  allocate( atmos_grid_cartesc_real_phi( ka,ia,ja) )
171 
172  allocate( atmos_grid_cartesc_real_area( ia,ja) )
177  allocate( atmos_grid_cartesc_real_areauy( ia,ja) )
180  allocate( atmos_grid_cartesc_real_areaxv( ia,ja) )
183 
186 
187  allocate( atmos_grid_cartesc_real_vol( ka,ia,ja) )
188  allocate( atmos_grid_cartesc_real_volwxy(0:ka,ia,ja) )
189  allocate( atmos_grid_cartesc_real_volzuy( ka,ia,ja) )
190  allocate( atmos_grid_cartesc_real_volzxv( ka,ia,ja) )
191 
193 
194  ! setup map projection
196 
197  ! calc longitude & latitude
198  call atmos_grid_cartesc_real_calc_latlon( domain_catalogue_fname, domain_catalogue_output )
199 
200  ! calc real height
202 
203  call interp_vert_setcoef( ka, ks, ke, ia, 1, ia, ja, 1, ja, & ! [IN]
204  topography_exist, & ! [IN]
205  atmos_grid_cartesc_cz(:), & ! [IN]
206  atmos_grid_cartesc_fz(:), & ! [IN]
207  atmos_grid_cartesc_real_cz(:,:,:), & ! [IN]
208  atmos_grid_cartesc_real_fz(:,:,:) ) ! [IN]
209 
210  return
211  end subroutine atmos_grid_cartesc_real_setup
212 
213  !-----------------------------------------------------------------------------
215  subroutine atmos_grid_cartesc_real_calc_latlon( &
216  catalogue_fname, &
217  catalogue_output )
218  use scale_prc, only: &
219  prc_abort, &
220  prc_nprocs, &
222  use scale_const, only: &
223  pi => const_pi, &
224  d2r => const_d2r
225  use scale_atmos_grid_cartesc, only: &
230  use scale_comm_cartesc, only: &
231  comm_gather, &
232  comm_bcast
233  use scale_mapprojection, only: &
236  mapprojection_xy2lonlat
237  implicit none
238 
239  character(len=*), intent(in) :: catalogue_fname
240  logical, intent(in) :: catalogue_output
241 
242  integer, parameter :: i_min = 1
243  integer, parameter :: i_max = 2
244  integer, parameter :: i_lon = 1
245  integer, parameter :: i_lat = 2
246 
247  real(rp) :: mine (2,2)
248  real(rp) :: whole(2,2,prc_nprocs)
249 
250  integer :: i, j
251  integer :: fid, ierr
252  !---------------------------------------------------------------------------
253 
256 
257  log_newline
258  log_info("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'Base position in the global domain (lat,lon)'
260 
261  !$omp parallel do collapse(2)
262  do j = 1, ja
263  do i = 1, ia
265  enddo
266  enddo
267 
268  !$omp parallel do collapse(2)
269  do j = 1, ja
270  do i = 0, ia
272  enddo
273  enddo
274 
275  !$omp parallel do collapse(2)
276  do j = 0, ja
277  do i = 1, ia
279  enddo
280  enddo
281 
282  !$omp parallel do collapse(2)
283  do j = 0, ja
284  do i = 0, ia
286  enddo
287  enddo
288 
289  !$omp workshare
290 !OCL ZFILL
291  atmos_grid_cartesc_real_dlon(:,:) = 0.0_rp
292 !OCL ZFILL
293  atmos_grid_cartesc_real_dlat(:,:) = 0.0_rp
294  !$omp end workshare
295 
296  !$omp parallel do
297  do j = js, je
298  do i = is, ie
302 
303  if ( atmos_grid_cartesc_real_dlon(i,j) == 0.0_rp &
304  .OR. atmos_grid_cartesc_real_dlat(i,j) == 0.0_rp ) then
305  log_error("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'Invalid grid distance in lat-lon! i,j=', i,j
306  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
307  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
308  call prc_abort
309  endif
310  enddo
311  enddo
312 
313  log_newline
314  log_info("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'Position on the earth (Local)'
315  log_info_cont('(1x,A,F10.5,A,F9.5,A,A,F10.5,A,F9.5,A)') &
318 
319  log_info_cont('(1x,A)') ' | |'
320  log_info_cont('(1x,A,F10.5,A,F9.5,A,A,F10.5,A,F9.5,A)') &
323 
324  mine(i_min,i_lon) = minval(atmos_grid_cartesc_real_lonuv(:,:)) / d2r
325  mine(i_max,i_lon) = maxval(atmos_grid_cartesc_real_lonuv(:,:)) / d2r
326  mine(i_min,i_lat) = minval(atmos_grid_cartesc_real_latuv(:,:)) / d2r
327  mine(i_max,i_lat) = maxval(atmos_grid_cartesc_real_latuv(:,:)) / d2r
328 
329  call comm_gather( whole(:,:,:), mine(:,:), 2, 2 ) ! everytime do for online nesting
330 
331  if ( prc_ismaster ) then
332  if ( catalogue_output ) then
333 
334  fid = io_get_available_fid()
335  open( fid, &
336  file = trim(catalogue_fname), &
337  form = 'formatted', &
338  status = 'replace', &
339  iostat = ierr )
340 
341  if ( ierr /= 0 ) then
342  log_error("ATMOS_GRID_CARTESC_REAL_calc_latlon",*) 'cannot create latlon-catalogue file!'
343  call prc_abort
344  endif
345 
346  do i = 1, prc_nprocs ! for offline nesting
347  write(fid,'(I8,8F32.24)',iostat=ierr) i, whole(i_min,i_lon,i), whole(i_max,i_lon,i), & ! LON: MIN, MAX
348  whole(i_min,i_lat,i), whole(i_max,i_lat,i) ! LAT: MIN, MAX
349  if ( ierr /= 0 ) exit
350  enddo
351 
352  close(fid)
353 
354  endif
355 
356  do i = 1, prc_nprocs ! for online nesting
357  atmos_grid_cartesc_real_domain_catalogue(i,i_min,i_lon) = whole(i_min,i_lon,i)
358  atmos_grid_cartesc_real_domain_catalogue(i,i_max,i_lon) = whole(i_max,i_lon,i)
359  atmos_grid_cartesc_real_domain_catalogue(i,i_min,i_lat) = whole(i_min,i_lat,i)
360  atmos_grid_cartesc_real_domain_catalogue(i,i_max,i_lat) = whole(i_max,i_lat,i)
361  enddo
362  endif
363 
364  call comm_bcast( atmos_grid_cartesc_real_domain_catalogue(:,:,:), prc_nprocs, 2, 2 )
365 
366  return
367  end subroutine atmos_grid_cartesc_real_calc_latlon
368 
369  !-----------------------------------------------------------------------------
372  use scale_const, only: &
373  grav => const_grav
374  use scale_atmos_grid_cartesc, only: &
379  use scale_file_cartesc, only: &
381  use scale_topography, only: &
382  zsfc => topography_zsfc
383  use scale_landuse, only: &
385  implicit none
386 
387  real(dp) :: htop
388  real(rp) :: zs
389  real(rp) :: dfz
390 
391  real(rp) :: dz1, dz2
392 
393  integer :: k, i, j
394  !---------------------------------------------------------------------------
395 
397 
398  !$omp parallel do private(zs) collapse(2)
399  do j = 1, ja
400  do i = 1, ia
401  zs = zsfc(i,j)
402  do k = 1, ka
403  atmos_grid_cartesc_real_cz(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
404  enddo
405  enddo
406  enddo
407 
408  !$omp parallel do private(zs) collapse(2)
409  do j = 1, ja
410  do i = 1, ia-1
411  zs = ( zsfc(i,j) + zsfc(i+1,j) ) * 0.5_rp
412  do k = 1, ka
413  atmos_grid_cartesc_real_czuy(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
414  enddo
415  enddo
416  enddo
417  !$omp parallel do private(zs)
418  do j = 1, ja
419  zs = zsfc(ia,j)
420  do k = 1, ka
421  atmos_grid_cartesc_real_czuy(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
422  enddo
423  enddo
424 
425  !$omp parallel do private(zs) collapse(2)
426  do j = 1, ja-1
427  do i = 1, ia
428  zs = ( zsfc(i,j) + zsfc(i,j+1) ) * 0.5_rp
429  do k = 1, ka
430  atmos_grid_cartesc_real_czxv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
431  enddo
432  enddo
433  enddo
434  do i = 1, ia
435  zs = zsfc(i,ja)
436  do k = 1, ka
437  atmos_grid_cartesc_real_czxv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
438  enddo
439  enddo
440 
441  !$omp parallel do private(zs) collapse(2)
442  do j = 1, ja-1
443  do i = 1, ia-1
444  zs = ( zsfc(i,j) + zsfc(i+1,j) + zsfc(i,j+1) + zsfc(i+1,j+1) ) * 0.25_rp
445  do k = 1, ka
446  atmos_grid_cartesc_real_czuv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
447  enddo
448  enddo
449  enddo
450  !$omp parallel do private(zs)
451  do j = 1, ja-1
452  zs = ( zsfc(ia,j) + zsfc(ia,j+1) ) * 0.5_rp
453  do k = 1, ka
454  atmos_grid_cartesc_real_czuv(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
455  enddo
456  enddo
457  do i = 1, ia-1
458  zs = ( zsfc(i,ja) + zsfc(i+1,ja) ) * 0.5_rp
459  do k = 1, ka
460  atmos_grid_cartesc_real_czuv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
461  enddo
462  enddo
463  zs = zsfc(ia,ja)
464  do k = 1, ka
465  atmos_grid_cartesc_real_czuv(k,ia,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
466  enddo
467 
468 
469  !$omp parallel do private(zs) collapse(2)
470  do j = 1, ja
471  do i = 1, ia
472  zs = zsfc(i,j)
473  do k = 0, ka
474  atmos_grid_cartesc_real_fz(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
475  end do
476  end do
477  end do
478 
479  !$omp parallel do private(zs) collapse(2)
480  do j = 1, ja
481  do i = 1, ia-1
482  zs = ( zsfc(i,j) + zsfc(i+1,j) ) * 0.5_rp
483  do k = 0, ka
484  atmos_grid_cartesc_real_fzuy(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
485  end do
486  end do
487  end do
488  !$omp parallel do private(zs)
489  do j = 1, ja
490  zs = zsfc(ia,j)
491  do k = 0, ka
492  atmos_grid_cartesc_real_fzuy(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
493  end do
494  end do
495 
496  !$omp parallel do private(zs) collapse(2)
497  do j = 1, ja-1
498  do i = 1, ia
499  zs = ( zsfc(i,j) + zsfc(i,j+1) ) * 0.5_rp
500  do k = 0, ka
501  atmos_grid_cartesc_real_fzxv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
502  enddo
503  enddo
504  enddo
505  !$omp parallel do private(zs)
506  do i = 1, ia
507  zs = zsfc(i,ja)
508  do k = 0, ka
509  atmos_grid_cartesc_real_fzxv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
510  enddo
511  enddo
512 
513  !$omp parallel do private(zs) collapse(2)
514  do j = 1, ja-1
515  do i = 1, ia-1
516  zs = ( zsfc(i,j) + zsfc(i+1,j) + zsfc(i,j+1) + zsfc(i+1,j+1) ) * 0.25_rp
517  do k = 0, ka
518  atmos_grid_cartesc_real_fzuv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
519  enddo
520  enddo
521  enddo
522  !$omp parallel do private(zs)
523  do j = 1, ja-1
524  zs = ( zsfc(ia,j) + zsfc(ia,j+1) ) * 0.5_rp
525  do k = 0, ka
526  atmos_grid_cartesc_real_fzuv(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
527  enddo
528  enddo
529  !$omp parallel do private(zs)
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  !$omp parallel do private(dz1,dz2) collapse(2)
542  do j = 1, ja
543  do i = 1, ia
544  do k = ks, ke-1
547  atmos_grid_cartesc_real_f2h(k,1,i,j) = dz2 / ( dz1 + dz2 )
548  atmos_grid_cartesc_real_f2h(k,2,i,j) = dz1 / ( dz1 + dz2 )
549  end do
550  atmos_grid_cartesc_real_f2h(1:ks-1,1,i,j) = 0.5_rp
551  atmos_grid_cartesc_real_f2h(1:ks-1,2,i,j) = 0.5_rp
552  atmos_grid_cartesc_real_f2h(ke:ka ,1,i,j) = 0.5_rp
553  atmos_grid_cartesc_real_f2h(ke:ka ,2,i,j) = 0.5_rp
554  end do
555  end do
556 
557 
558  !$omp workshare
559 !OCL ZFILL
561 
562 !OCL ZFILL
564  !$omp end workshare
565 
568 
569  !$omp parallel do private(dfz) collapse(2) &
570  !$omp reduction(max:ATMOS_GRID_CARTESC_REAL_ASPECT_MAX) &
571  !$omp reduction(min:ATMOS_GRID_CARTESC_REAL_ASPECT_MIN)
572  do j = js, je
573  do i = is, ie
574  do k = ks, ke
578  enddo
579  enddo
580  enddo
581 
582  log_newline
583  log_info("ATMOS_GRID_CARTESC_REAL_calc_Z",*) 'Minimum & maximum lowermost CZ'
584  log_info_cont(*) '-> (',minval( atmos_grid_cartesc_real_cz(ks,:,:) ),',',maxval( atmos_grid_cartesc_real_cz(ks,:,:) ),')'
585  log_info("ATMOS_GRID_CARTESC_REAL_calc_Z",*) 'Minimum & maximum aspect ratio'
587 
588  ! set latlon and z to fileio module
592  zsfc, landuse_frac_land ) ! [IN]
593 
594  return
595  end subroutine atmos_grid_cartesc_real_calc_z
596 
597  !-----------------------------------------------------------------------------
600  MAPF )
601  use scale_prc_cartesc, only: &
602  prc_twod
603  use scale_atmos_grid_cartesc, only: &
608  use scale_comm_cartesc, only: &
609  comm_vars8, &
610  comm_wait
611  use scale_file_cartesc, only: &
613  use scale_topography, only: &
615  use scale_landuse, only: &
617  implicit none
618 
619  real(rp), intent(in) :: mapf(ia,ja,2,4)
620 
621  real(rp) :: areauv(ia,ja)
622 
623  integer :: k, i, j
624  !---------------------------------------------------------------------------
625 
626  atmos_grid_cartesc_real_area(:,:) = 0.0_rp
627  atmos_grid_cartesc_real_areazuy_x(:,:,:) = 0.0_rp
628  atmos_grid_cartesc_real_areazxv_y(:,:,:) = 0.0_rp
629  atmos_grid_cartesc_real_areawuy_x(:,:,:) = 0.0_rp
630  atmos_grid_cartesc_real_areawxv_y(:,:,:) = 0.0_rp
631  atmos_grid_cartesc_real_areauy(:,:) = 0.0_rp
632  atmos_grid_cartesc_real_areazxy_x(:,:,:) = 0.0_rp
633  atmos_grid_cartesc_real_areazuv_y(:,:,:) = 0.0_rp
634  atmos_grid_cartesc_real_areaxv(:,:) = 0.0_rp
635  atmos_grid_cartesc_real_areazuv_y(:,:,:) = 0.0_rp
636  atmos_grid_cartesc_real_areazxy_y(:,:,:) = 0.0_rp
637 
643 
644  atmos_grid_cartesc_real_vol(:,:,:) = 0.0_rp
645  atmos_grid_cartesc_real_volwxy(:,:,:) = 0.0_rp
646  atmos_grid_cartesc_real_volzuy(:,:,:) = 0.0_rp
647  atmos_grid_cartesc_real_volzxv(:,:,:) = 0.0_rp
652 
653  !$omp parallel do
654  do j = js, je
655  do i = is, ie
656  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) )
657  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) )
658  end do
659  end do
660  if ( prc_twod ) then
661  !$omp parallel do
662  do j = js, je
663  do i = is, ie
665  areauv(i,j) = atmos_grid_cartesc_real_areaxv(i,j)
666 
667  end do
668  end do
669  else
670  !$omp parallel do
671  do j = js, je
672  do i = is, ie
673  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) )
674  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) )
675 
676  end do
677  end do
678  end if
679 
680  call comm_vars8( atmos_grid_cartesc_real_area(:,:), 1 )
681  call comm_vars8( atmos_grid_cartesc_real_areaxv(:,:), 2 )
682  call comm_vars8( atmos_grid_cartesc_real_areauy(:,:), 3 )
683  call comm_vars8( areauv(:,:), 4 )
684 
685  !$omp parallel do &
686  !$omp reduction(+:ATMOS_GRID_CARTESC_REAL_TOTAREA,ATMOS_GRID_CARTESC_REAL_TOTAREAXV,ATMOS_GRID_CARTESC_REAL_TOTAREAUY)
687  do j = js, je
688  do i = is, ie
692  end do
693  end do
694 
695  !$omp parallel do collapse(2)
696  do j = 1, ja
697  do i = 1, ia
698  do k = ks, ke
700  end do
701  do k = ks-1, ke
703  end do
704  do k = ks, ke
707  end do
708  end do
709  end do
710 
711  if ( .not. prc_twod ) then
712  !$omp parallel do collapse(2)
713  do j = 1, ja
714  do i = 1, ia
715  do k = ks, ke
717  end do
718  do k = ks-1, ke
720  end do
721  do k = ks, ke
724  end do
725  end do
726  end do
727  end if
728 
729  call comm_wait( atmos_grid_cartesc_real_area(:,:), 1 )
730  call comm_wait( atmos_grid_cartesc_real_areaxv(:,:), 2 )
731  call comm_wait( atmos_grid_cartesc_real_areauy(:,:), 3 )
732  call comm_wait( areauv(:,:), 4 )
733 
734 
735  !$omp parallel do collapse(2)
736  do j = 1, ja
737  do i = is, ie
738  do k = ks, ke
740  end do
741  end do
742  end do
743  !$omp parallel do collapse(2)
744  do j = js, je
745  do i = 1, ia
746  do k = ks, ke
748  end do
749  end do
750  end do
751 
752 
753  !$omp parallel do collapse(2)
754  do j = 1, ja
755  do i = 1, ia
756  do k = ks, ke
759  end do
760  do k = ks-1, ke
762  end do
763  end do
764  end do
765  if ( prc_twod ) then
766  !$omp parallel do collapse(2)
767  do j = 1, ja
768  do i = 1, ia
769  do k = ks, ke
771  end do
772  end do
773  end do
774  else
775  !$omp parallel do collapse(2)
776  do j = 1, ja
777  do i = 1, ia
778  do k = ks, ke
780  end do
781  end do
782  end do
783  end if
784 
785  !$omp parallel do &
786  !$omp reduction(+:ATMOS_GRID_CARTESC_REAL_TOTVOL,ATMOS_GRID_CARTESC_REAL_TOTVOLZXV,ATMOS_GRID_CARTESC_REAL_TOTVOLWXY,ATMOS_GRID_CARTESC_REAL_TOTVOLZUY)
787  do j = js, je
788  do i = is, ie
789  do k = ks, ke
794  enddo
795  enddo
796  enddo
797 
798  ! set latlon and z to fileio module
804 
805  return
807 
scale_const::const_grav
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:46
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxy_y
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_y
virtical area (zxy, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:75
scale_atmos_grid_cartesc_index::i_uy
integer, public i_uy
Definition: scale_atmos_grid_cartesC_index.F90:99
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_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fzuy
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzuy
geopotential height [m] (wuy)
Definition: scale_atmos_grid_cartesC_real.F90:43
scale_atmos_grid_cartesc_index::i_xv
integer, public i_xv
Definition: scale_atmos_grid_cartesC_index.F90:100
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvolzxv
real(rp), public atmos_grid_cartesc_real_totvolzxv
total volume (zxv, local) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:90
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_cz
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
Definition: scale_atmos_grid_cartesC_real.F90:38
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_volwxy
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volwxy
control volume (wxy) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:84
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_z1
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_z1
Height of the lowermost grid from surface (cell center) [m].
Definition: scale_atmos_grid_cartesC_real.F90:59
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_aspect_min
real(rp), public atmos_grid_cartesc_real_aspect_min
minimum aspect ratio of the grid cell
Definition: scale_atmos_grid_cartesC_real.F90:61
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_real::atmos_grid_cartesc_real_lonxv
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonxv
longitude at staggered point (xv) [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:50
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areawuy_x
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawuy_x
virtical area (wuy, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:68
scale_atmos_grid_cartesc_index::i_uv
integer, public i_uv
Definition: scale_atmos_grid_cartesC_index.F90:101
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totarea
real(rp), public atmos_grid_cartesc_real_totarea
total area (xy, local) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:77
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvolwxy
real(rp), public atmos_grid_cartesc_real_totvolwxy
total volume (wxy, local) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:88
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_real::atmos_grid_cartesc_real_dlon
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_dlon
delta longitude
Definition: scale_atmos_grid_cartesC_real.F90:56
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_topography
module TOPOGRAPHY
Definition: scale_topography.F90:11
scale_io::io_get_available_fid
integer function, public io_get_available_fid()
search & get available file ID
Definition: scale_io.F90:321
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_calc_areavol
subroutine, public atmos_grid_cartesc_real_calc_areavol(MAPF)
Calc control area/volume.
Definition: scale_atmos_grid_cartesC_real.F90:601
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_basepoint_lat
real(rp), public atmos_grid_cartesc_real_basepoint_lat
position of base point in real world [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:36
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_czxv
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czxv
geopotential height [m] (zxv)
Definition: scale_atmos_grid_cartesC_real.F90:40
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lon
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
longitude [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:48
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_basepoint_lon
real(rp), public atmos_grid_cartesc_real_basepoint_lon
position of base point in real world [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:35
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_volzuy
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzuy
control volume (zuy) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:85
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_real::atmos_grid_cartesc_real_domain_catalogue
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_domain_catalogue
domain latlon catalogue [rad]
Definition: scale_atmos_grid_cartesC_real.F90:92
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_const::const_pi
real(rp), public const_pi
pi
Definition: scale_const.F90:31
scale_atmos_grid_cartesc_index::i_xy
integer, public i_xy
Definition: scale_atmos_grid_cartesC_index.F90:98
scale_mapprojection::mapprojection_basepoint_lat
real(rp), public mapprojection_basepoint_lat
Definition: scale_mapprojection.F90:91
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_aspect_max
real(rp), public atmos_grid_cartesc_real_aspect_max
maximum aspect ratio of the grid cell
Definition: scale_atmos_grid_cartesC_real.F90:60
scale_mapprojection
module Map projection
Definition: scale_mapprojection.F90:12
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_io
module STDIO
Definition: scale_io.F90:10
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fzxv
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzxv
geopotential height [m] (wxv)
Definition: scale_atmos_grid_cartesC_real.F90:44
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_real::atmos_grid_cartesc_real_volzxv
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzxv
control volume (zxv) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:86
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_vol
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:83
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_czuv
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czuv
geopotential height [m] (zuv)
Definition: scale_atmos_grid_cartesC_real.F90:41
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latuv
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuv
latitude at staggered point (uv) [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:55
scale_landuse::landuse_frac_land
real(rp), dimension(:,:), allocatable, public landuse_frac_land
land fraction
Definition: scale_landuse.F90:54
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areawxv_y
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawxv_y
virtical area (wxv, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:69
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuy_x
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuy_x
virtical area (zuy, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:66
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_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latuy
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuy
latitude at staggered point (uy) [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:53
scale_prc_cartesc
module process / cartesC
Definition: scale_prc_cartesC.F90:11
scale_mapprojection::mapprojection_setup
subroutine, public mapprojection_setup(DOMAIN_CENTER_X, DOMAIN_CENTER_Y)
Setup.
Definition: scale_mapprojection.F90:194
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_setup
subroutine, public atmos_grid_cartesc_real_setup
Setup.
Definition: scale_atmos_grid_cartesC_real.F90:109
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_area
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
horizontal area ( xy, normal z) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:65
scale_topography::topography_exist
logical, public topography_exist
topography exists?
Definition: scale_topography.F90:36
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_precision::dp
integer, parameter, public dp
Definition: scale_precision.F90:32
scale_mapprojection::mapprojection_basepoint_lon
real(rp), public mapprojection_basepoint_lon
Definition: scale_mapprojection.F90:90
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareauy
real(rp), public atmos_grid_cartesc_real_totareauy
total area (uy, local) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:78
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvolzuy
real(rp), public atmos_grid_cartesc_real_totvolzuy
total volume (zuy, local) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:89
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_real::atmos_grid_cartesc_real_areauy
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areauy
horizontal area ( uy, normal z) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:70
scale_file_cartesc::file_cartesc_set_coordinates_atmos
subroutine, public file_cartesc_set_coordinates_atmos(CZ, FZ, LON, LONUY, LONXV, LONUV, LAT, LATUY, LATXV, LATUV, TOPO, LSMASK)
set latlon and z for atmosphere
Definition: scale_file_cartesC.F90:454
scale_file_cartesc::file_cartesc_set_areavol_atmos
subroutine, public file_cartesc_set_areavol_atmos(AREA, AREAZUY_X, AREAZXV_Y, AREAWUY_X, AREAWXV_Y, AREAUY, AREAZXY_X, AREAZUV_Y, AREAXV, AREAZUV_X, AREAZXY_Y, VOL, VOLWXY, VOLZUY, VOLZXV)
set area and volume
Definition: scale_file_cartesC.F90:500
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuv_x
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_x
virtical area (zuv, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:74
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_dlat
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_dlat
delta latitude
Definition: scale_atmos_grid_cartesC_real.F90:57
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latxv
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latxv
latitude at staggered point (xv) [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:54
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_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuv_y
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_y
virtical area (zuv, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:72
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_f2h
real(rp), dimension(:,:,:,:), allocatable, public atmos_grid_cartesc_real_f2h
coefficient for interpolation from full to half levels
Definition: scale_atmos_grid_cartesC_real.F90:46
scale_topography::topography_zsfc
real(rp), dimension(:,:), allocatable, public topography_zsfc
absolute ground height [m]
Definition: scale_topography.F90:38
scale_prc::prc_nprocs
integer, public prc_nprocs
myrank in local communicator
Definition: scale_prc.F90:89
scale_interp_vert::interp_vert_setcoef
subroutine, public interp_vert_setcoef(KA, KS, KE, IA, IS, IE, JA, JS, JE, TOPO_exist, Xi, Xih, Z, Zh)
Setup.
Definition: scale_interp_vert.F90:86
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_calc_z
subroutine, public atmos_grid_cartesc_real_calc_z
Convert Xi to Z coordinate.
Definition: scale_atmos_grid_cartesC_real.F90:372
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_comm_cartesc
module COMMUNICATION
Definition: scale_comm_cartesC.F90:11
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lonuv
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuv
longitude at staggered point (uv) [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:51
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxy_x
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_x
virtical area (zxy, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:71
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_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_real::atmos_grid_cartesc_real_totareazuy_x
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_real_totareazuy_x
total area (zuy, normal x) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:80
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareaxv
real(rp), public atmos_grid_cartesc_real_totareaxv
total area (xv, local) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:79
scale_const::const_d2r
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:32
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_phi
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_phi
geopotential [m2/s2] (cell center)
Definition: scale_atmos_grid_cartesC_real.F90:63
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areaxv
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areaxv
horizontal area ( xv, normal z) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:73
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_real::atmos_grid_cartesc_real_lat
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
Definition: scale_atmos_grid_cartesC_real.F90:52
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fz
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
Definition: scale_atmos_grid_cartesC_real.F90:42
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvol
real(rp), public atmos_grid_cartesc_real_totvol
total volume (zxy, local) [m3]
Definition: scale_atmos_grid_cartesC_real.F90:87
scale_atmos_grid_cartesc
module atmosphere / grid / cartesC
Definition: scale_atmos_grid_cartesC.F90:12
scale_landuse
module LANDUSE
Definition: scale_landuse.F90:19
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_real::atmos_grid_cartesc_real_areazxv_y
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxv_y
virtical area (zxv, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:67
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fzuv
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzuv
geopotential height [m] (wuv)
Definition: scale_atmos_grid_cartesC_real.F90:45
scale_interp_vert
module INTERPOLATION vertical
Definition: scale_interp_vert.F90:11
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_prc_cartesc::prc_twod
logical, public prc_twod
2D experiment
Definition: scale_prc_cartesC.F90:55
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11
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_prc::prc_ismaster
logical, public prc_ismaster
master process in local communicator?
Definition: scale_prc.F90:91
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lonuy
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuy
longitude at staggered point (uy) [rad,0-2pi]
Definition: scale_atmos_grid_cartesC_real.F90:49
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_czuy
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czuy
geopotential height [m] (zuy)
Definition: scale_atmos_grid_cartesC_real.F90:39
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazxv_y
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_real_totareazxv_y
total area (zxv, normal y) [m2]
Definition: scale_atmos_grid_cartesC_real.F90:81