SCALE-RM
Functions/Subroutines | Variables
scale_atmos_grid_cartesc_real Module Reference

module Atmosphere GRID CartesC Real(real space) More...

Functions/Subroutines

subroutine, public atmos_grid_cartesc_real_setup
 Setup. More...
 
subroutine, public atmos_grid_cartesc_real_calc_z
 Convert Xi to Z coordinate. More...
 
subroutine, public atmos_grid_cartesc_real_calc_areavol (MAPF)
 Calc control area/volume. More...
 
subroutine, public atmos_grid_cartesc_real_finalize
 Finalize. More...
 

Variables

real(rp), public atmos_grid_cartesc_real_basepoint_lon
 position of base point in real world [rad,0-2pi] More...
 
real(rp), public atmos_grid_cartesc_real_basepoint_lat
 position of base point in real world [rad,-pi,pi] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
 geopotential height [m] (zxy) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czuy
 geopotential height [m] (zuy) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czxv
 geopotential height [m] (zxv) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_czuv
 geopotential height [m] (zuv) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
 geopotential height [m] (wxy) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzuy
 geopotential height [m] (wuy) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzxv
 geopotential height [m] (wxv) More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fzuv
 geopotential height [m] (wuv) More...
 
real(rp), dimension(:,:,:,:), allocatable, public atmos_grid_cartesc_real_f2h
 coefficient for interpolation from full to half levels More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
 longitude [rad,0-2pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuy
 longitude at staggered point (uy) [rad,0-2pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonxv
 longitude at staggered point (xv) [rad,0-2pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuv
 longitude at staggered point (uv) [rad,0-2pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
 latitude [rad,-pi,pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuy
 latitude at staggered point (uy) [rad,-pi,pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latxv
 latitude at staggered point (xv) [rad,-pi,pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuv
 latitude at staggered point (uv) [rad,-pi,pi] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_dlon
 delta longitude More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_dlat
 delta latitude More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_z1
 Height of the lowermost grid from surface (cell center) [m]. More...
 
real(rp), public atmos_grid_cartesc_real_aspect_max
 maximum aspect ratio of the grid cell More...
 
real(rp), public atmos_grid_cartesc_real_aspect_min
 minimum aspect ratio of the grid cell More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_phi
 geopotential [m2/s2] (cell center) More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
 horizontal area ( xy, normal z) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuy_x
 virtical area (zuy, normal x) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxv_y
 virtical area (zxv, normal y) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawuy_x
 virtical area (wuy, normal x) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawxv_y
 virtical area (wxv, normal y) [m2] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areauy
 horizontal area ( uy, normal z) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_x
 virtical area (zxy, normal x) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_y
 virtical area (zuv, normal y) [m2] More...
 
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areaxv
 horizontal area ( xv, normal z) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_x
 virtical area (zuv, normal x) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_y
 virtical area (zxy, normal y) [m2] More...
 
real(rp), public atmos_grid_cartesc_real_totarea
 total area (xy, local) [m2] More...
 
real(rp), public atmos_grid_cartesc_real_totareauy
 total area (uy, local) [m2] More...
 
real(rp), public atmos_grid_cartesc_real_totareaxv
 total area (xv, local) [m2] More...
 
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_real_totareazuy_x
 total area (zuy, normal x) [m2] More...
 
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_real_totareazxv_y
 total area (zxv, normal y) [m2] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
 control volume (zxy) [m3] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volwxy
 control volume (wxy) [m3] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzuy
 control volume (zuy) [m3] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzxv
 control volume (zxv) [m3] More...
 
real(rp), public atmos_grid_cartesc_real_totvol
 total volume (zxy, local) [m3] More...
 
real(rp), public atmos_grid_cartesc_real_totvolwxy
 total volume (wxy, local) [m3] More...
 
real(rp), public atmos_grid_cartesc_real_totvolzuy
 total volume (zuy, local) [m3] More...
 
real(rp), public atmos_grid_cartesc_real_totvolzxv
 total volume (zxv, local) [m3] More...
 
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_domain_catalogue
 domain latlon catalogue [rad] More...
 

Detailed Description

module Atmosphere GRID CartesC Real(real space)

Description
Grid module for orthogonal curvelinear, terrain-following coordinate
Author
Team SCALE
NAMELIST
  • PARAM_DOMAIN_CATALOGUE
    nametypedefault valuecomment
    DOMAIN_CATALOGUE_FNAME character(len=H_LONG) 'latlon_domain_catalogue.txt' metadata files for lat-lon domain for all processes
    DOMAIN_CATALOGUE_OUTPUT logical .false.

History Output
No history output

Function/Subroutine Documentation

◆ atmos_grid_cartesc_real_setup()

subroutine, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_setup

Setup.

Definition at line 110 of file scale_atmos_grid_cartesC_real.F90.

110  use scale_prc, only: &
111  prc_nprocs, &
112  prc_abort
113  use scale_atmos_grid_cartesc, only: &
114  atmos_grid_cartesc_domain_center_x, &
115  atmos_grid_cartesc_domain_center_y, &
116  atmos_grid_cartesc_cz, &
117  atmos_grid_cartesc_fz
118  use scale_topography, only: &
120  use scale_mapprojection, only: &
122  use scale_interp_vert, only: &
124  implicit none
125 
126  character(len=H_LONG) :: DOMAIN_CATALOGUE_FNAME = 'latlon_domain_catalogue.txt'
127  logical :: DOMAIN_CATALOGUE_OUTPUT = .false.
128 
129  namelist / param_domain_catalogue / &
130  domain_catalogue_fname, &
131  domain_catalogue_output
132 
133  integer :: ierr
134  !---------------------------------------------------------------------------
135 
136  log_newline
137  log_info("ATMOS_GRID_CARTESC_REAL_setup",*) 'Setup'
138 
139  !--- read namelist
140  rewind(io_fid_conf)
141  read(io_fid_conf,nml=param_domain_catalogue,iostat=ierr)
142  if( ierr < 0 ) then !--- missing
143  log_info("ATMOS_GRID_CARTESC_REAL_setup",*) 'Not found namelist. Default used.'
144  elseif( ierr > 0 ) then !--- fatal error
145  log_error("ATMOS_GRID_CARTESC_REAL_setup",*) 'Not appropriate names in namelist PARAM_DOMAIN_CATALOGUE. Check!'
146  call prc_abort
147  endif
148  log_nml(param_domain_catalogue)
149 
150  allocate( atmos_grid_cartesc_real_lon( ia, ja) )
151  allocate( atmos_grid_cartesc_real_lat( ia, ja) )
152  allocate( atmos_grid_cartesc_real_lonuy(0:ia, ja) )
153  allocate( atmos_grid_cartesc_real_lonxv( ia,0:ja) )
154  allocate( atmos_grid_cartesc_real_lonuv(0:ia,0:ja) )
155  allocate( atmos_grid_cartesc_real_latuy(0:ia, ja) )
156  allocate( atmos_grid_cartesc_real_latxv( ia,0:ja) )
157  allocate( atmos_grid_cartesc_real_latuv(0:ia,0:ja) )
158  allocate( atmos_grid_cartesc_real_dlon( ia, ja) )
159  allocate( atmos_grid_cartesc_real_dlat( ia, ja) )
160  !$acc enter data create(ATMOS_GRID_CARTESC_REAL_LON, ATMOS_GRID_CARTESC_REAL_LAT, ATMOS_GRID_CARTESC_REAL_LONUY, ATMOS_GRID_CARTESC_REAL_LONXV, ATMOS_GRID_CARTESC_REAL_LONUV, ATMOS_GRID_CARTESC_REAL_LATUY, ATMOS_GRID_CARTESC_REAL_LATXV, ATMOS_GRID_CARTESC_REAL_LATUV, ATMOS_GRID_CARTESC_REAL_DLON, ATMOS_GRID_CARTESC_REAL_DLAT)
161 
162  allocate( atmos_grid_cartesc_real_cz( ka,ia,ja) )
163  allocate( atmos_grid_cartesc_real_czuy( ka,ia,ja) )
164  allocate( atmos_grid_cartesc_real_czxv( ka,ia,ja) )
165  allocate( atmos_grid_cartesc_real_czuv( ka,ia,ja) )
166  allocate( atmos_grid_cartesc_real_fz(0:ka,ia,ja) )
167  allocate( atmos_grid_cartesc_real_fzuy(0:ka,ia,ja) )
168  allocate( atmos_grid_cartesc_real_fzxv(0:ka,ia,ja) )
169  allocate( atmos_grid_cartesc_real_fzuv(0:ka,ia,ja) )
170  allocate( atmos_grid_cartesc_real_f2h(ka,2,ia,ja) )
171  allocate( atmos_grid_cartesc_real_z1( ia,ja) )
172  allocate( atmos_grid_cartesc_real_phi( ka,ia,ja) )
173  !$acc enter data create(ATMOS_GRID_CARTESC_REAL_CZ, ATMOS_GRID_CARTESC_REAL_CZUY, ATMOS_GRID_CARTESC_REAL_CZXV, ATMOS_GRID_CARTESC_REAL_CZUV, ATMOS_GRID_CARTESC_REAL_FZ, ATMOS_GRID_CARTESC_REAL_FZUY, ATMOS_GRID_CARTESC_REAL_FZXV, ATMOS_GRID_CARTESC_REAL_FZUV, ATMOS_GRID_CARTESC_REAL_F2H, ATMOS_GRID_CARTESC_REAL_Z1, ATMOS_GRID_CARTESC_REAL_PHI)
174 
175  allocate( atmos_grid_cartesc_real_area( ia,ja) )
176  allocate( atmos_grid_cartesc_real_areazuy_x(ka ,ia,ja) )
177  allocate( atmos_grid_cartesc_real_areazxv_y(ka ,ia,ja) )
178  allocate( atmos_grid_cartesc_real_areawuy_x(ka+1,ia,ja) )
179  allocate( atmos_grid_cartesc_real_areawxv_y(ka+1,ia,ja) )
180  allocate( atmos_grid_cartesc_real_areauy( ia,ja) )
181  allocate( atmos_grid_cartesc_real_areazxy_x(ka, ia,ja) )
182  allocate( atmos_grid_cartesc_real_areazuv_y(ka, ia,ja) )
183  allocate( atmos_grid_cartesc_real_areaxv( ia,ja) )
184  allocate( atmos_grid_cartesc_real_areazuv_x(ka, ia,ja) )
185  allocate( atmos_grid_cartesc_real_areazxy_y(ka, ia,ja) )
186  !$acc enter data create(ATMOS_GRID_CARTESC_REAL_AREA, ATMOS_GRID_CARTESC_REAL_AREAZUY_X, ATMOS_GRID_CARTESC_REAL_AREAZXV_Y, ATMOS_GRID_CARTESC_REAL_AREAWUY_X, ATMOS_GRID_CARTESC_REAL_AREAWXV_Y, ATMOS_GRID_CARTESC_REAL_AREAUY, ATMOS_GRID_CARTESC_REAL_AREAZXY_X, ATMOS_GRID_CARTESC_REAL_AREAZUV_Y, ATMOS_GRID_CARTESC_REAL_AREAXV, ATMOS_GRID_CARTESC_REAL_AREAZUV_X, ATMOS_GRID_CARTESC_REAL_AREAZXY_Y)
187 
188  allocate( atmos_grid_cartesc_real_totareazuy_x(ia) )
189  allocate( atmos_grid_cartesc_real_totareazxv_y(ja) )
190  !$acc enter data create(ATMOS_GRID_CARTESC_REAL_TOTAREAZUY_X, ATMOS_GRID_CARTESC_REAL_TOTAREAZXV_Y)
191 
192  allocate( atmos_grid_cartesc_real_vol( ka,ia,ja) )
193  allocate( atmos_grid_cartesc_real_volwxy(0:ka,ia,ja) )
194  allocate( atmos_grid_cartesc_real_volzuy( ka,ia,ja) )
195  allocate( atmos_grid_cartesc_real_volzxv( ka,ia,ja) )
196  !$acc enter data create(ATMOS_GRID_CARTESC_REAL_VOL, ATMOS_GRID_CARTESC_REAL_VOLWXY, ATMOS_GRID_CARTESC_REAL_VOLZUY, ATMOS_GRID_CARTESC_REAL_VOLZXV)
197 
198  allocate( atmos_grid_cartesc_real_domain_catalogue(prc_nprocs,2,2) )
199 
200  ! setup map projection
201  call mapprojection_setup( atmos_grid_cartesc_domain_center_x, atmos_grid_cartesc_domain_center_y )
202 
203  ! calc longitude & latitude
204  call atmos_grid_cartesc_real_calc_latlon( domain_catalogue_fname, domain_catalogue_output )
205 
206  ! calc real height
207  call atmos_grid_cartesc_real_calc_z
208 
209  call interp_vert_setcoef( ka, ks, ke, ia, 1, ia, ja, 1, ja, & ! [IN]
210  topography_exist, & ! [IN]
211  atmos_grid_cartesc_cz(:), & ! [IN]
212  atmos_grid_cartesc_fz(:), & ! [IN]
213  atmos_grid_cartesc_real_cz(:,:,:), & ! [IN]
214  atmos_grid_cartesc_real_fz(:,:,:) ) ! [IN]
215 
216  return

References scale_atmos_grid_cartesc::atmos_grid_cartesc_cx, scale_atmos_grid_cartesc::atmos_grid_cartesc_cy, scale_atmos_grid_cartesc::atmos_grid_cartesc_cz, scale_atmos_grid_cartesc::atmos_grid_cartesc_domain_center_x, scale_atmos_grid_cartesc::atmos_grid_cartesc_domain_center_y, scale_atmos_grid_cartesc::atmos_grid_cartesc_fx, scale_atmos_grid_cartesc::atmos_grid_cartesc_fy, scale_atmos_grid_cartesc::atmos_grid_cartesc_fz, atmos_grid_cartesc_real_area, atmos_grid_cartesc_real_areauy, atmos_grid_cartesc_real_areawuy_x, atmos_grid_cartesc_real_areawxv_y, atmos_grid_cartesc_real_areaxv, atmos_grid_cartesc_real_areazuv_x, atmos_grid_cartesc_real_areazuv_y, atmos_grid_cartesc_real_areazuy_x, atmos_grid_cartesc_real_areazxv_y, atmos_grid_cartesc_real_areazxy_x, atmos_grid_cartesc_real_areazxy_y, atmos_grid_cartesc_real_basepoint_lat, atmos_grid_cartesc_real_basepoint_lon, atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_cz, atmos_grid_cartesc_real_czuv, atmos_grid_cartesc_real_czuy, atmos_grid_cartesc_real_czxv, atmos_grid_cartesc_real_dlat, atmos_grid_cartesc_real_dlon, atmos_grid_cartesc_real_domain_catalogue, atmos_grid_cartesc_real_f2h, atmos_grid_cartesc_real_fz, atmos_grid_cartesc_real_fzuv, atmos_grid_cartesc_real_fzuy, atmos_grid_cartesc_real_fzxv, atmos_grid_cartesc_real_lat, atmos_grid_cartesc_real_latuv, atmos_grid_cartesc_real_latuy, atmos_grid_cartesc_real_latxv, atmos_grid_cartesc_real_lon, atmos_grid_cartesc_real_lonuv, atmos_grid_cartesc_real_lonuy, atmos_grid_cartesc_real_lonxv, atmos_grid_cartesc_real_phi, atmos_grid_cartesc_real_totareazuy_x, atmos_grid_cartesc_real_totareazxv_y, atmos_grid_cartesc_real_vol, atmos_grid_cartesc_real_volwxy, atmos_grid_cartesc_real_volzuy, atmos_grid_cartesc_real_volzxv, atmos_grid_cartesc_real_z1, scale_const::const_d2r, scale_const::const_pi, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_interp_vert::interp_vert_setcoef(), scale_io::io_fid_conf, scale_io::io_get_available_fid(), scale_io::io_get_fname(), scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_atmos_grid_cartesc_index::ka, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, scale_mapprojection::mapprojection_basepoint_lat, scale_mapprojection::mapprojection_basepoint_lon, scale_mapprojection::mapprojection_setup(), scale_prc::prc_abort(), scale_prc::prc_ismaster, scale_prc::prc_nprocs, and scale_topography::topography_exist.

Referenced by mod_rm_driver::rm_driver(), and mod_rm_prep::rm_prep().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_grid_cartesc_real_calc_z()

subroutine, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_calc_z

Convert Xi to Z coordinate.

Definition at line 388 of file scale_atmos_grid_cartesC_real.F90.

388  use scale_const, only: &
389  grav => const_grav
390  use scale_atmos_grid_cartesc, only: &
391  atmos_grid_cartesc_cz, &
392  atmos_grid_cartesc_fz, &
393  atmos_grid_cartesc_cdx, &
394  atmos_grid_cartesc_cdy
395  use scale_file_cartesc, only: &
397  use scale_topography, only: &
398  zsfc => topography_zsfc
399  use scale_landuse, only: &
401  implicit none
402 
403  real(DP) :: Htop
404  real(RP) :: Zs
405  real(RP) :: DFZ
406 
407  real(RP) :: dz1, dz2
408 
409  integer :: k, i, j
410  !---------------------------------------------------------------------------
411 
412  htop = atmos_grid_cartesc_fz(ke) - atmos_grid_cartesc_fz(ks-1)
413 
414  !$omp parallel do private(zs) collapse(2)
415  do j = 1, ja
416  do i = 1, ia
417  zs = zsfc(i,j)
418  do k = 1, ka
419  atmos_grid_cartesc_real_cz(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
420  enddo
421  enddo
422  enddo
423  !$acc update device(ATMOS_GRID_CARTESC_REAL_CZ) async
424 
425  !$omp parallel do private(zs) collapse(2)
426  do j = 1, ja
427  do i = 1, ia-1
428  zs = ( zsfc(i,j) + zsfc(i+1,j) ) * 0.5_rp
429  do k = 1, ka
430  atmos_grid_cartesc_real_czuy(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
431  enddo
432  enddo
433  enddo
434  !$omp parallel do private(zs)
435  do j = 1, ja
436  zs = zsfc(ia,j)
437  do k = 1, ka
438  atmos_grid_cartesc_real_czuy(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
439  enddo
440  enddo
441  !$acc update device(ATMOS_GRID_CARTESC_REAL_CZUY) async
442 
443  !$omp parallel do private(zs) collapse(2)
444  do j = 1, ja-1
445  do i = 1, ia
446  zs = ( zsfc(i,j) + zsfc(i,j+1) ) * 0.5_rp
447  do k = 1, ka
448  atmos_grid_cartesc_real_czxv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
449  enddo
450  enddo
451  enddo
452  do i = 1, ia
453  zs = zsfc(i,ja)
454  do k = 1, ka
455  atmos_grid_cartesc_real_czxv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
456  enddo
457  enddo
458  !$acc update device(ATMOS_GRID_CARTESC_REAL_CZXV) async
459 
460  !$omp parallel do private(zs) collapse(2)
461  do j = 1, ja-1
462  do i = 1, ia-1
463  zs = ( zsfc(i,j) + zsfc(i+1,j) + zsfc(i,j+1) + zsfc(i+1,j+1) ) * 0.25_rp
464  do k = 1, ka
465  atmos_grid_cartesc_real_czuv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
466  enddo
467  enddo
468  enddo
469  !$omp parallel do private(zs)
470  do j = 1, ja-1
471  zs = ( zsfc(ia,j) + zsfc(ia,j+1) ) * 0.5_rp
472  do k = 1, ka
473  atmos_grid_cartesc_real_czuv(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
474  enddo
475  enddo
476  do i = 1, ia-1
477  zs = ( zsfc(i,ja) + zsfc(i+1,ja) ) * 0.5_rp
478  do k = 1, ka
479  atmos_grid_cartesc_real_czuv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
480  enddo
481  enddo
482  zs = zsfc(ia,ja)
483  do k = 1, ka
484  atmos_grid_cartesc_real_czuv(k,ia,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_cz(k) + zs
485  enddo
486  !$acc update device(ATMOS_GRID_CARTESC_REAL_CZUV) async
487 
488  !$omp parallel do private(zs) collapse(2)
489  do j = 1, ja
490  do i = 1, ia
491  zs = zsfc(i,j)
492  do k = 0, ka
493  atmos_grid_cartesc_real_fz(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
494  end do
495  end do
496  end do
497  !$acc update device(ATMOS_GRID_CARTESC_REAL_FZ) async
498 
499  !$omp parallel do private(zs) collapse(2)
500  do j = 1, ja
501  do i = 1, ia-1
502  zs = ( zsfc(i,j) + zsfc(i+1,j) ) * 0.5_rp
503  do k = 0, ka
504  atmos_grid_cartesc_real_fzuy(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
505  end do
506  end do
507  end do
508  !$omp parallel do private(zs)
509  do j = 1, ja
510  zs = zsfc(ia,j)
511  do k = 0, ka
512  atmos_grid_cartesc_real_fzuy(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
513  end do
514  end do
515  !$acc update device(ATMOS_GRID_CARTESC_REAL_FZUY) async
516 
517  !$omp parallel do private(zs) collapse(2)
518  do j = 1, ja-1
519  do i = 1, ia
520  zs = ( zsfc(i,j) + zsfc(i,j+1) ) * 0.5_rp
521  do k = 0, ka
522  atmos_grid_cartesc_real_fzxv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
523  enddo
524  enddo
525  enddo
526  !$omp parallel do private(zs)
527  do i = 1, ia
528  zs = zsfc(i,ja)
529  do k = 0, ka
530  atmos_grid_cartesc_real_fzxv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
531  enddo
532  enddo
533  !$acc update device(ATMOS_GRID_CARTESC_REAL_FZXV) async
534 
535  !$omp parallel do private(zs) collapse(2)
536  do j = 1, ja-1
537  do i = 1, ia-1
538  zs = ( zsfc(i,j) + zsfc(i+1,j) + zsfc(i,j+1) + zsfc(i+1,j+1) ) * 0.25_rp
539  do k = 0, ka
540  atmos_grid_cartesc_real_fzuv(k,i,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
541  enddo
542  enddo
543  enddo
544  !$omp parallel do private(zs)
545  do j = 1, ja-1
546  zs = ( zsfc(ia,j) + zsfc(ia,j+1) ) * 0.5_rp
547  do k = 0, ka
548  atmos_grid_cartesc_real_fzuv(k,ia,j) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
549  enddo
550  enddo
551  !$omp parallel do private(zs)
552  do i = 1, ia-1
553  zs = ( zsfc(i,ja) + zsfc(i+1,ja) ) * 0.5_rp
554  do k = 0, ka
555  atmos_grid_cartesc_real_fzuv(k,i,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
556  enddo
557  enddo
558  zs = zsfc(ia,ja)
559  do k = 0, ka
560  atmos_grid_cartesc_real_fzuv(k,ia,ja) = ( htop - zs ) / htop * atmos_grid_cartesc_fz(k) + zs
561  enddo
562  !$acc update device(ATMOS_GRID_CARTESC_REAL_FZUV) async
563 
564  !$omp parallel do private(dz1,dz2) collapse(2)
565  do j = 1, ja
566  do i = 1, ia
567  do k = ks, ke-1
568  dz1 = atmos_grid_cartesc_real_fz(k+1,i,j) - atmos_grid_cartesc_real_fz(k ,i,j)
569  dz2 = atmos_grid_cartesc_real_fz(k ,i,j) - atmos_grid_cartesc_real_fz(k-1,i,j)
570  atmos_grid_cartesc_real_f2h(k,1,i,j) = dz2 / ( dz1 + dz2 )
571  atmos_grid_cartesc_real_f2h(k,2,i,j) = dz1 / ( dz1 + dz2 )
572  end do
573  atmos_grid_cartesc_real_f2h(1:ks-1,1,i,j) = 0.5_rp
574  atmos_grid_cartesc_real_f2h(1:ks-1,2,i,j) = 0.5_rp
575  atmos_grid_cartesc_real_f2h(ke:ka ,1,i,j) = 0.5_rp
576  atmos_grid_cartesc_real_f2h(ke:ka ,2,i,j) = 0.5_rp
577  end do
578  end do
579  !$acc update device(ATMOS_GRID_CARTESC_REAL_F2H) async
580 
581  !$omp workshare
582 !OCL ZFILL
583  atmos_grid_cartesc_real_z1(:,:) = atmos_grid_cartesc_real_cz(ks,:,:) - zsfc(:,:)
584  !$acc update device(ATMOS_GRID_CARTESC_REAL_Z1) async
585 
586 !OCL ZFILL
587  atmos_grid_cartesc_real_phi(:,:,:) = grav * atmos_grid_cartesc_real_cz(:,:,:)
588  !$omp end workshare
589  !$acc update device(ATMOS_GRID_CARTESC_REAL_Z1, ATMOS_GRID_CARTESC_REAL_PHI) async
590 
591  atmos_grid_cartesc_real_aspect_max = -1.e+30_rp
592  atmos_grid_cartesc_real_aspect_min = 1.e+30_rp
593 
594  !$omp parallel do private(dfz) collapse(2) &
595  !$omp reduction(max:ATMOS_GRID_CARTESC_REAL_ASPECT_MAX) &
596  !$omp reduction(min:ATMOS_GRID_CARTESC_REAL_ASPECT_MIN)
597  do j = js, je
598  do i = is, ie
599  do k = ks, ke
600  dfz = atmos_grid_cartesc_real_fz(k,i,j) - atmos_grid_cartesc_real_fz(k-1,i,j)
601  atmos_grid_cartesc_real_aspect_max = max( atmos_grid_cartesc_real_aspect_max, atmos_grid_cartesc_cdx(i) / dfz, atmos_grid_cartesc_cdy(j) / dfz )
602  atmos_grid_cartesc_real_aspect_min = min( atmos_grid_cartesc_real_aspect_min, atmos_grid_cartesc_cdx(i) / dfz, atmos_grid_cartesc_cdy(j) / dfz )
603  enddo
604  enddo
605  enddo
606 
607  log_newline
608  log_info("ATMOS_GRID_CARTESC_REAL_calc_Z",*) 'Minimum & maximum lowermost CZ'
609  log_info_cont(*) '-> (',minval( atmos_grid_cartesc_real_cz(ks,:,:) ),',',maxval( atmos_grid_cartesc_real_cz(ks,:,:) ),')'
610  log_info("ATMOS_GRID_CARTESC_REAL_calc_Z",*) 'Minimum & maximum aspect ratio'
611  log_info_cont(*) '-> (',atmos_grid_cartesc_real_aspect_min,',',atmos_grid_cartesc_real_aspect_max,')'
612 
613  ! set latlon and z to fileio module
614  call file_cartesc_set_coordinates_atmos( atmos_grid_cartesc_real_cz, atmos_grid_cartesc_real_fz, & ! [IN]
615  atmos_grid_cartesc_real_lon, atmos_grid_cartesc_real_lonuy, atmos_grid_cartesc_real_lonxv, atmos_grid_cartesc_real_lonuv, & ! [IN]
616  atmos_grid_cartesc_real_lat, atmos_grid_cartesc_real_latuy, atmos_grid_cartesc_real_latxv, atmos_grid_cartesc_real_latuv, & ! [IN]
617  zsfc, landuse_frac_land ) ! [IN]
618 
619  !$acc wait
620 
621  return

References scale_atmos_grid_cartesc::atmos_grid_cartesc_cdx, scale_atmos_grid_cartesc::atmos_grid_cartesc_cdy, scale_atmos_grid_cartesc::atmos_grid_cartesc_cz, scale_atmos_grid_cartesc::atmos_grid_cartesc_fz, atmos_grid_cartesc_real_aspect_max, atmos_grid_cartesc_real_aspect_min, atmos_grid_cartesc_real_cz, atmos_grid_cartesc_real_czuv, atmos_grid_cartesc_real_czuy, atmos_grid_cartesc_real_czxv, atmos_grid_cartesc_real_f2h, atmos_grid_cartesc_real_fz, atmos_grid_cartesc_real_fzuv, atmos_grid_cartesc_real_fzuy, atmos_grid_cartesc_real_fzxv, atmos_grid_cartesc_real_lat, atmos_grid_cartesc_real_latuv, atmos_grid_cartesc_real_latuy, atmos_grid_cartesc_real_latxv, atmos_grid_cartesc_real_lon, atmos_grid_cartesc_real_lonuv, atmos_grid_cartesc_real_lonuy, atmos_grid_cartesc_real_lonxv, atmos_grid_cartesc_real_phi, atmos_grid_cartesc_real_z1, scale_const::const_grav, scale_file_cartesc::file_cartesc_set_coordinates_atmos(), scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_tracer::k, scale_atmos_grid_cartesc_index::ka, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, scale_landuse::landuse_frac_land, and scale_topography::topography_zsfc.

Referenced by atmos_grid_cartesc_real_setup(), and mod_rm_prep::rm_prep().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_grid_cartesc_real_calc_areavol()

subroutine, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_calc_areavol ( real(rp), dimension(ia,ja,2,4), intent(in)  MAPF)

Calc control area/volume.

Definition at line 628 of file scale_atmos_grid_cartesC_real.F90.

628  use scale_prc_cartesc, only: &
629  prc_twod
630  use scale_const, &
631  undef => const_undef
632  use scale_atmos_grid_cartesc, only: &
633  atmos_grid_cartesc_cdx, &
634  atmos_grid_cartesc_fdx, &
635  atmos_grid_cartesc_cdy, &
636  atmos_grid_cartesc_fdy
637  use scale_comm_cartesc, only: &
638  comm_vars8, &
639  comm_wait
640  use scale_file_cartesc, only: &
642  use scale_topography, only: &
644  use scale_landuse, only: &
646  implicit none
647 
648  real(RP), intent(in) :: MAPF(IA,JA,2,4)
649 
650  real(RP) :: AREAUV(IA,JA)
651 
652  integer :: k, i, j
653  !---------------------------------------------------------------------------
654 
655  atmos_grid_cartesc_real_area(:,:) = 0.0_rp
656  atmos_grid_cartesc_real_areazuy_x(:,:,:) = 0.0_rp
657  atmos_grid_cartesc_real_areazxv_y(:,:,:) = 0.0_rp
658  atmos_grid_cartesc_real_areawuy_x(:,:,:) = 0.0_rp
659  atmos_grid_cartesc_real_areawxv_y(:,:,:) = 0.0_rp
660  atmos_grid_cartesc_real_areauy(:,:) = 0.0_rp
661  atmos_grid_cartesc_real_areazxy_x(:,:,:) = 0.0_rp
662  atmos_grid_cartesc_real_areazuv_y(:,:,:) = 0.0_rp
663  atmos_grid_cartesc_real_areaxv(:,:) = 0.0_rp
664  atmos_grid_cartesc_real_areazuv_y(:,:,:) = 0.0_rp
665  atmos_grid_cartesc_real_areazxy_y(:,:,:) = 0.0_rp
666 
667  atmos_grid_cartesc_real_totarea = 0.0_rp
668  atmos_grid_cartesc_real_totareauy = 0.0_rp
669  atmos_grid_cartesc_real_totareaxv = 0.0_rp
670  atmos_grid_cartesc_real_totareazuy_x(:) = 0.0_rp
671  atmos_grid_cartesc_real_totareazxv_y(:) = 0.0_rp
672 
673  atmos_grid_cartesc_real_vol(:,:,:) = 0.0_rp
674  atmos_grid_cartesc_real_volwxy(:,:,:) = 0.0_rp
675  atmos_grid_cartesc_real_volzuy(:,:,:) = 0.0_rp
676  atmos_grid_cartesc_real_volzxv(:,:,:) = 0.0_rp
677  atmos_grid_cartesc_real_totvol = 0.0_rp
678  atmos_grid_cartesc_real_totvolwxy = 0.0_rp
679  atmos_grid_cartesc_real_totvolzuy = 0.0_rp
680  atmos_grid_cartesc_real_totvolzxv = 0.0_rp
681 
682  !$omp parallel do
683  do j = js, je
684  do i = is, ie
685  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) )
686  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) )
687  end do
688  end do
689  if ( prc_twod ) then
690  !$omp parallel do
691  do j = js, je
692  do i = is, ie
693  atmos_grid_cartesc_real_areauy(i,j) = atmos_grid_cartesc_real_area(i,j)
694  areauv(i,j) = atmos_grid_cartesc_real_areaxv(i,j)
695 
696  end do
697  end do
698  else
699  !$omp parallel do
700  do j = js, je
701  do i = is, ie
702  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) )
703  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) )
704 
705  end do
706  end do
707  end if
708 
709 #ifdef QUICKDEBUG
710  atmos_grid_cartesc_real_area(1:is-1,:) = undef
711  atmos_grid_cartesc_real_area(ie+1:ia,:) = undef
712  atmos_grid_cartesc_real_area(:,1:js-1) = undef
713  atmos_grid_cartesc_real_area(:,je+1:ja) = undef
714  atmos_grid_cartesc_real_areaxv(1:is-1,:) = undef
715  atmos_grid_cartesc_real_areaxv(ie+1:ia,:) = undef
716  atmos_grid_cartesc_real_areaxv(:,1:js-1) = undef
717  atmos_grid_cartesc_real_areaxv(:,je+1:ja) = undef
718  atmos_grid_cartesc_real_areauy(1:is-1,:) = undef
719  atmos_grid_cartesc_real_areauy(ie+1:ia,:) = undef
720  atmos_grid_cartesc_real_areauy(:,1:js-1) = undef
721  atmos_grid_cartesc_real_areauy(:,je+1:ja) = undef
722  areauv(1:is-1,:) = undef
723  areauv(ie+1:ia,:) = undef
724  areauv(:,1:js-1) = undef
725  areauv(:,je+1:ja) = undef
726 #endif
727  call comm_vars8( atmos_grid_cartesc_real_area(:,:), 1 )
728  call comm_vars8( atmos_grid_cartesc_real_areaxv(:,:), 2 )
729  call comm_vars8( atmos_grid_cartesc_real_areauy(:,:), 3 )
730  call comm_vars8( areauv(:,:), 4 )
731 
732  !$omp parallel do &
733  !$omp reduction(+:ATMOS_GRID_CARTESC_REAL_TOTAREA,ATMOS_GRID_CARTESC_REAL_TOTAREAXV,ATMOS_GRID_CARTESC_REAL_TOTAREAUY)
734  do j = js, je
735  do i = is, ie
736  atmos_grid_cartesc_real_totarea = atmos_grid_cartesc_real_totarea + atmos_grid_cartesc_real_area(i,j)
737  atmos_grid_cartesc_real_totareaxv = atmos_grid_cartesc_real_totareaxv + atmos_grid_cartesc_real_areaxv(i,j)
738  atmos_grid_cartesc_real_totareauy = atmos_grid_cartesc_real_totareauy + atmos_grid_cartesc_real_areauy(i,j)
739  end do
740  end do
741 
742  !$omp parallel do collapse(2)
743  do j = 1, ja
744  do i = 1, ia
745  do k = ks, ke
746  atmos_grid_cartesc_real_areazxv_y(k,i,j) = atmos_grid_cartesc_cdx(i) / mapf(i,j,1,i_xv) * ( atmos_grid_cartesc_real_fzxv(k,i,j) - atmos_grid_cartesc_real_fzxv(k-1,i,j) )
747  end do
748  do k = ks-1, ke
749  atmos_grid_cartesc_real_areawxv_y(k,i,j) = atmos_grid_cartesc_cdx(i) / mapf(i,j,1,i_xv) * ( atmos_grid_cartesc_real_czxv(k+1,i,j) - atmos_grid_cartesc_real_czxv(k,i,j) )
750  end do
751  do k = ks, ke
752  atmos_grid_cartesc_real_areazxy_x(k,i,j) = atmos_grid_cartesc_cdy(j) / mapf(i,j,2,i_xy) * ( atmos_grid_cartesc_real_fz(k,i,j) - atmos_grid_cartesc_real_fz(k-1,i,j) )
753  atmos_grid_cartesc_real_areazxy_y(k,i,j) = atmos_grid_cartesc_cdx(i) / mapf(i,j,1,i_xy) * ( atmos_grid_cartesc_real_fz(k,i,j) - atmos_grid_cartesc_real_fz(k-1,i,j) )
754  end do
755  end do
756  end do
757  !$acc update device(ATMOS_GRID_CARTESC_REAL_AREAZXV_Y, ATMOS_GRID_CARTESC_REAL_AREAWXV_Y, ATMOS_GRID_CARTESC_REAL_AREAZXY_X, ATMOS_GRID_CARTESC_REAL_AREAZXY_Y) async
758 
759  !$omp parallel do collapse(2)
760  do j = 1, ja
761  do i = 1, ia
762  do k = ks, ke
763  atmos_grid_cartesc_real_areazuy_x(k,i,j) = atmos_grid_cartesc_cdy(j) / mapf(i,j,2,i_uy) * ( atmos_grid_cartesc_real_fzuy(k,i,j) - atmos_grid_cartesc_real_fzuy(k-1,i,j) )
764  end do
765  do k = ks-1, ke
766  atmos_grid_cartesc_real_areawuy_x(k,i,j) = atmos_grid_cartesc_cdy(j) / mapf(i,j,2,i_uy) * ( atmos_grid_cartesc_real_czuy(k+1,i,j) - atmos_grid_cartesc_real_czuy(k,i,j) )
767  end do
768  do k = ks, ke
769  atmos_grid_cartesc_real_areazuv_y(k,i,j) = atmos_grid_cartesc_cdx(i) / mapf(i,j,1,i_uv) * ( atmos_grid_cartesc_real_fzuv(k,i,j) - atmos_grid_cartesc_real_fzuv(k-1,i,j) )
770  atmos_grid_cartesc_real_areazuv_x(k,i,j) = atmos_grid_cartesc_cdy(j) / mapf(i,j,2,i_uv) * ( atmos_grid_cartesc_real_fzuv(k,i,j) - atmos_grid_cartesc_real_fzuv(k-1,i,j) )
771  end do
772  end do
773  end do
774  !$acc update device(ATMOS_GRID_CARTESC_REAL_AREAZUY_X, ATMOS_GRID_CARTESC_REAL_AREAWUY_X, ATMOS_GRID_CARTESC_REAL_AREAZUV_Y, ATMOS_GRID_CARTESC_REAL_AREAZUV_X) async
775 
776  call comm_wait( atmos_grid_cartesc_real_area(:,:), 1 )
777  call comm_wait( atmos_grid_cartesc_real_areaxv(:,:), 2 )
778  call comm_wait( atmos_grid_cartesc_real_areauy(:,:), 3 )
779  call comm_wait( areauv(:,:), 4 )
780  !$acc update device(ATMOS_GRID_CARTESC_REAL_AREA, ATMOS_GRID_CARTESC_REAL_AREAXV, ATMOS_GRID_CARTESC_REAL_AREAUY) async
781 
782 
783  !$omp parallel do collapse(2)
784  do j = 1, ja
785  do i = is, ie
786  do k = ks, ke
787  atmos_grid_cartesc_real_totareazxv_y(j) = atmos_grid_cartesc_real_totareazxv_y(j) + atmos_grid_cartesc_real_areazxv_y(k,i,j)
788  end do
789  end do
790  end do
791  !$omp parallel do collapse(2)
792  do j = js, je
793  do i = 1, ia
794  do k = ks, ke
795  atmos_grid_cartesc_real_totareazuy_x(i) = atmos_grid_cartesc_real_totareazuy_x(i) + atmos_grid_cartesc_real_areazuy_x(k,i,j)
796  end do
797  end do
798  end do
799  !$acc update device(ATMOS_GRID_CARTESC_REAL_TOTAREAZXV_Y, ATMOS_GRID_CARTESC_REAL_TOTAREAZUY_X) async
800 
801 
802  !$omp parallel do collapse(2)
803  do j = 1, ja
804  do i = 1, ia
805  do k = ks, ke
806  atmos_grid_cartesc_real_vol(k,i,j) = ( atmos_grid_cartesc_real_fz(k,i,j) - atmos_grid_cartesc_real_fz(k-1,i,j) ) * atmos_grid_cartesc_real_area(i,j)
807  atmos_grid_cartesc_real_volzxv(k,i,j) = ( atmos_grid_cartesc_real_fzxv(k,i,j) - atmos_grid_cartesc_real_fzxv(k-1,i,j) ) * atmos_grid_cartesc_real_areaxv(i,j)
808  end do
809  do k = ks-1, ke
810  atmos_grid_cartesc_real_volwxy(k,i,j) = ( atmos_grid_cartesc_real_cz(k+1,i,j) - atmos_grid_cartesc_real_cz(k,i,j) ) * atmos_grid_cartesc_real_area(i,j)
811  end do
812  end do
813  end do
814  if ( prc_twod ) then
815  !$omp parallel do collapse(2)
816  do j = 1, ja
817  do i = 1, ia
818  do k = ks, ke
819  atmos_grid_cartesc_real_volzuy(k,i,j) = atmos_grid_cartesc_real_vol(k,i,j)
820  end do
821  end do
822  end do
823  else
824  !$omp parallel do collapse(2)
825  do j = 1, ja
826  do i = 1, ia
827  do k = ks, ke
828  atmos_grid_cartesc_real_volzuy(k,i,j) = ( atmos_grid_cartesc_real_fzuy(k,i,j) - atmos_grid_cartesc_real_fzuy(k-1,i,j) ) * atmos_grid_cartesc_real_areauy(i,j)
829  end do
830  end do
831  end do
832  end if
833  !$acc update device(ATMOS_GRID_CARTESC_REAL_VOL, ATMOS_GRID_CARTESC_REAL_VOLZXV, ATMOS_GRID_CARTESC_REAL_VOLWXY, ATMOS_GRID_CARTESC_REAL_VOLZUY) async
834 
835  !$omp parallel do &
836  !$omp reduction(+:ATMOS_GRID_CARTESC_REAL_TOTVOL,ATMOS_GRID_CARTESC_REAL_TOTVOLZXV,ATMOS_GRID_CARTESC_REAL_TOTVOLWXY,ATMOS_GRID_CARTESC_REAL_TOTVOLZUY)
837  do j = js, je
838  do i = is, ie
839  do k = ks, ke
840  atmos_grid_cartesc_real_totvol = atmos_grid_cartesc_real_totvol + atmos_grid_cartesc_real_vol(k,i,j)
841  atmos_grid_cartesc_real_totvolzxv = atmos_grid_cartesc_real_totvolzxv + atmos_grid_cartesc_real_volzxv(k,i,j)
842  atmos_grid_cartesc_real_totvolwxy = atmos_grid_cartesc_real_totvolwxy + atmos_grid_cartesc_real_volwxy(k,i,j)
843  atmos_grid_cartesc_real_totvolzuy = atmos_grid_cartesc_real_totvolzuy + atmos_grid_cartesc_real_volzuy(k,i,j)
844  enddo
845  enddo
846  enddo
847 
848  ! set latlon and z to fileio module
849  call file_cartesc_set_areavol_atmos( atmos_grid_cartesc_real_area, atmos_grid_cartesc_real_areazuy_x, atmos_grid_cartesc_real_areazxv_y, & ! [IN]
850  atmos_grid_cartesc_real_areawuy_x, atmos_grid_cartesc_real_areawxv_y, & ! [IN]
851  atmos_grid_cartesc_real_areauy, atmos_grid_cartesc_real_areazxy_x, atmos_grid_cartesc_real_areazuv_y, & ! [IN]
852  atmos_grid_cartesc_real_areaxv, atmos_grid_cartesc_real_areazuv_x, atmos_grid_cartesc_real_areazxy_y, & ! [IN]
853  atmos_grid_cartesc_real_vol, atmos_grid_cartesc_real_volwxy, atmos_grid_cartesc_real_volzuy, atmos_grid_cartesc_real_volzxv ) ! [IN]
854 
855  !$acc wait
856 
857  return

References scale_atmos_grid_cartesc::atmos_grid_cartesc_cdx, scale_atmos_grid_cartesc::atmos_grid_cartesc_cdy, scale_atmos_grid_cartesc::atmos_grid_cartesc_fdx, scale_atmos_grid_cartesc::atmos_grid_cartesc_fdy, atmos_grid_cartesc_real_area, atmos_grid_cartesc_real_areauy, atmos_grid_cartesc_real_areawuy_x, atmos_grid_cartesc_real_areawxv_y, atmos_grid_cartesc_real_areaxv, atmos_grid_cartesc_real_areazuv_x, atmos_grid_cartesc_real_areazuv_y, atmos_grid_cartesc_real_areazuy_x, atmos_grid_cartesc_real_areazxv_y, atmos_grid_cartesc_real_areazxy_x, atmos_grid_cartesc_real_areazxy_y, atmos_grid_cartesc_real_cz, atmos_grid_cartesc_real_czuy, atmos_grid_cartesc_real_czxv, atmos_grid_cartesc_real_fz, atmos_grid_cartesc_real_fzuv, atmos_grid_cartesc_real_fzuy, atmos_grid_cartesc_real_fzxv, atmos_grid_cartesc_real_totarea, atmos_grid_cartesc_real_totareauy, atmos_grid_cartesc_real_totareaxv, atmos_grid_cartesc_real_totareazuy_x, atmos_grid_cartesc_real_totareazxv_y, atmos_grid_cartesc_real_totvol, atmos_grid_cartesc_real_totvolwxy, atmos_grid_cartesc_real_totvolzuy, atmos_grid_cartesc_real_totvolzxv, atmos_grid_cartesc_real_vol, atmos_grid_cartesc_real_volwxy, atmos_grid_cartesc_real_volzuy, atmos_grid_cartesc_real_volzxv, scale_const::const_undef, scale_file_cartesc::file_cartesc_set_areavol_atmos(), scale_atmos_grid_cartesc_index::i_uv, scale_atmos_grid_cartesc_index::i_uy, scale_atmos_grid_cartesc_index::i_xv, scale_atmos_grid_cartesc_index::i_xy, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_tracer::k, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, scale_landuse::landuse_frac_land, scale_prc_cartesc::prc_twod, and scale_topography::topography_zsfc.

Referenced by mod_rm_driver::rm_driver(), and mod_rm_prep::rm_prep().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_grid_cartesc_real_finalize()

subroutine, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_finalize

Finalize.

Definition at line 863 of file scale_atmos_grid_cartesC_real.F90.

863  use scale_interp_vert, only: &
865  implicit none
866  !---------------------------------------------------------------------------
867 
868  !$acc exit data delete(ATMOS_GRID_CARTESC_REAL_LON, ATMOS_GRID_CARTESC_REAL_LAT, ATMOS_GRID_CARTESC_REAL_LONUY, ATMOS_GRID_CARTESC_REAL_LONXV, ATMOS_GRID_CARTESC_REAL_LONUV, ATMOS_GRID_CARTESC_REAL_LATUY, ATMOS_GRID_CARTESC_REAL_LATXV, ATMOS_GRID_CARTESC_REAL_LATUV, ATMOS_GRID_CARTESC_REAL_DLON, ATMOS_GRID_CARTESC_REAL_DLAT)
869  deallocate( atmos_grid_cartesc_real_lon )
870  deallocate( atmos_grid_cartesc_real_lat )
871  deallocate( atmos_grid_cartesc_real_lonuy )
872  deallocate( atmos_grid_cartesc_real_lonxv )
873  deallocate( atmos_grid_cartesc_real_lonuv )
874  deallocate( atmos_grid_cartesc_real_latuy )
875  deallocate( atmos_grid_cartesc_real_latxv )
876  deallocate( atmos_grid_cartesc_real_latuv )
877  deallocate( atmos_grid_cartesc_real_dlon )
878  deallocate( atmos_grid_cartesc_real_dlat )
879 
880  !$acc exit data delete(ATMOS_GRID_CARTESC_REAL_CZ, ATMOS_GRID_CARTESC_REAL_CZUY, ATMOS_GRID_CARTESC_REAL_CZXV, ATMOS_GRID_CARTESC_REAL_CZUV, ATMOS_GRID_CARTESC_REAL_FZ, ATMOS_GRID_CARTESC_REAL_FZUY, ATMOS_GRID_CARTESC_REAL_FZXV, ATMOS_GRID_CARTESC_REAL_FZUV, ATMOS_GRID_CARTESC_REAL_F2H, ATMOS_GRID_CARTESC_REAL_Z1, ATMOS_GRID_CARTESC_REAL_PHI)
881  deallocate( atmos_grid_cartesc_real_cz )
882  deallocate( atmos_grid_cartesc_real_czuy )
883  deallocate( atmos_grid_cartesc_real_czxv )
884  deallocate( atmos_grid_cartesc_real_czuv )
885  deallocate( atmos_grid_cartesc_real_fz )
886  deallocate( atmos_grid_cartesc_real_fzuy )
887  deallocate( atmos_grid_cartesc_real_fzxv )
888  deallocate( atmos_grid_cartesc_real_fzuv )
889  deallocate( atmos_grid_cartesc_real_f2h )
890  deallocate( atmos_grid_cartesc_real_z1 )
891  deallocate( atmos_grid_cartesc_real_phi )
892 
893  !acc exit data delete(ATMOS_GRID_CARTESC_REAL_AREA, ATMOS_GRID_CARTESC_REAL_AREAZUY_X, ATMOS_GRID_CARTESC_REAL_AREAZXV_Y, ATMOS_GRID_CARTESC_REAL_AREAWUY_X, ATMOS_GRID_CARTESC_REAL_AREAWXV_Y, ATMOS_GRID_CARTESC_REAL_AREAUY, ATMOS_GRID_CARTESC_REAL_AREAZXY_X, ATMOS_GRID_CARTESC_REAL_AREAZUV_Y, ATMOS_GRID_CARTESC_REAL_AREAXV, ATMOS_GRID_CARTESC_REAL_AREAZUV_X, ATMOS_GRID_CARTESC_REAL_ZXY_Y)
894  deallocate( atmos_grid_cartesc_real_area )
895  deallocate( atmos_grid_cartesc_real_areazuy_x )
896  deallocate( atmos_grid_cartesc_real_areazxv_y )
897  deallocate( atmos_grid_cartesc_real_areawuy_x )
898  deallocate( atmos_grid_cartesc_real_areawxv_y )
899  deallocate( atmos_grid_cartesc_real_areauy )
900  deallocate( atmos_grid_cartesc_real_areazxy_x )
901  deallocate( atmos_grid_cartesc_real_areazuv_y )
902  deallocate( atmos_grid_cartesc_real_areaxv )
903  deallocate( atmos_grid_cartesc_real_areazuv_x )
904  deallocate( atmos_grid_cartesc_real_areazxy_y )
905 
906  !$acc exit data delete(ATMOS_GRID_CARTESC_REAL_TOTAREAZUY_X, ATMOS_GRID_CARTESC_REAL_TOTAREAZXV_Y)
907  deallocate( atmos_grid_cartesc_real_totareazuy_x )
908  deallocate( atmos_grid_cartesc_real_totareazxv_y )
909 
910  !$acc exit data delete(ATMOS_GRID_CARTESC_REAL_VOL, ATMOS_GRID_CARTESC_REAL_VOLWXY, ATMOS_GRID_CARTESC_REAL_VOLZUY, ATMOS_GRID_CARTESC_REAL_VOLZXV)
911  deallocate( atmos_grid_cartesc_real_vol )
912  deallocate( atmos_grid_cartesc_real_volwxy )
913  deallocate( atmos_grid_cartesc_real_volzuy )
914  deallocate( atmos_grid_cartesc_real_volzxv )
915 
916  deallocate( atmos_grid_cartesc_real_domain_catalogue )
917 
919 
920  return

References atmos_grid_cartesc_real_area, atmos_grid_cartesc_real_areauy, atmos_grid_cartesc_real_areawuy_x, atmos_grid_cartesc_real_areawxv_y, atmos_grid_cartesc_real_areaxv, atmos_grid_cartesc_real_areazuv_x, atmos_grid_cartesc_real_areazuv_y, atmos_grid_cartesc_real_areazuy_x, atmos_grid_cartesc_real_areazxv_y, atmos_grid_cartesc_real_areazxy_x, atmos_grid_cartesc_real_areazxy_y, atmos_grid_cartesc_real_cz, atmos_grid_cartesc_real_czuv, atmos_grid_cartesc_real_czuy, atmos_grid_cartesc_real_czxv, atmos_grid_cartesc_real_dlat, atmos_grid_cartesc_real_dlon, atmos_grid_cartesc_real_domain_catalogue, atmos_grid_cartesc_real_f2h, atmos_grid_cartesc_real_fz, atmos_grid_cartesc_real_fzuv, atmos_grid_cartesc_real_fzuy, atmos_grid_cartesc_real_fzxv, atmos_grid_cartesc_real_lat, atmos_grid_cartesc_real_latuv, atmos_grid_cartesc_real_latuy, atmos_grid_cartesc_real_latxv, atmos_grid_cartesc_real_lon, atmos_grid_cartesc_real_lonuv, atmos_grid_cartesc_real_lonuy, atmos_grid_cartesc_real_lonxv, atmos_grid_cartesc_real_phi, atmos_grid_cartesc_real_totareazuy_x, atmos_grid_cartesc_real_totareazxv_y, atmos_grid_cartesc_real_vol, atmos_grid_cartesc_real_volwxy, atmos_grid_cartesc_real_volzuy, atmos_grid_cartesc_real_volzxv, atmos_grid_cartesc_real_z1, and scale_interp_vert::interp_vert_finalize().

Referenced by mod_rm_driver::rm_driver(), and mod_rm_prep::rm_prep().

Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ atmos_grid_cartesc_real_basepoint_lon

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_basepoint_lon

position of base point in real world [rad,0-2pi]

Definition at line 36 of file scale_atmos_grid_cartesC_real.F90.

36  real(RP), public :: ATMOS_GRID_CARTESC_REAL_BASEPOINT_LON

Referenced by mod_atmos_driver::atmos_driver_setup(), scale_atmos_grid_cartesc_metric::atmos_grid_cartesc_metric_rotcoef(), and atmos_grid_cartesc_real_setup().

◆ atmos_grid_cartesc_real_basepoint_lat

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_basepoint_lat

◆ atmos_grid_cartesc_real_cz

real(rp), dimension (:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_cz

geopotential height [m] (zxy)

Definition at line 39 of file scale_atmos_grid_cartesC_real.F90.

39  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_CZ (:,:,:)

Referenced by mod_atmos_driver::atmos_driver_setup(), mod_atmos_driver::atmos_driver_update(), scale_atmos_grid_cartesc_metric::atmos_grid_cartesc_metric_rotcoef(), atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), mod_atmos_phy_bl_driver::atmos_phy_bl_driver_calc_tendency(), mod_atmos_phy_bl_driver::atmos_phy_bl_driver_mkinit(), mod_atmos_phy_cp_driver::atmos_phy_cp_driver_calc_tendency(), mod_atmos_phy_cp_driver::atmos_phy_cp_driver_setup(), mod_atmos_phy_mp_driver::atmos_phy_mp_driver_calc_tendency(), mod_atmos_phy_rd_driver::atmos_phy_rd_driver_calc_tendency(), mod_atmos_phy_sf_driver::atmos_phy_sf_driver_calc_tendency(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver_setup(), mod_atmos_vars::atmos_vars_calc_diagnostics(), mod_atmos_vars::atmos_vars_check(), mod_atmos_vars::atmos_vars_get_diagnostic_2d(), mod_atmos_vars::atmos_vars_get_diagnostic_3d(), mod_atmos_vars::atmos_vars_history(), mod_cnvuser::cnvuser(), com_gamma(), scale_comm_cartesc_nest::comm_cartesc_nest_domain_shape(), scale_comm_cartesc_nest::comm_cartesc_nest_intercomm_nestdown_3d(), scale_comm_cartesc_nest::comm_cartesc_nest_setup(), mod_da_driver::da_driver_update(), scale_file_history_cartesc::file_history_cartesc_truncate_3d(), mod_atmos_phy_sf_driver::history_output(), mod_realinput::realinput_surface(), mod_rm_driver::restart_read(), and scale_spnudge::spnudge_setup().

◆ atmos_grid_cartesc_real_czuy

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_czuy

◆ atmos_grid_cartesc_real_czxv

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_czxv

◆ atmos_grid_cartesc_real_czuv

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_czuv

geopotential height [m] (zuv)

Definition at line 42 of file scale_atmos_grid_cartesC_real.F90.

42  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_CZUV(:,:,:)

Referenced by scale_atmos_grid_cartesc_metric::atmos_grid_cartesc_metric_rotcoef(), atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_finalize(), and atmos_grid_cartesc_real_setup().

◆ atmos_grid_cartesc_real_fz

real(rp), dimension (:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fz

◆ atmos_grid_cartesc_real_fzuy

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fzuy

geopotential height [m] (wuy)

Definition at line 44 of file scale_atmos_grid_cartesC_real.F90.

44  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_FZUY(:,:,:)

Referenced by scale_atmos_grid_cartesc_metric::atmos_grid_cartesc_metric_rotcoef(), atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_finalize(), and atmos_grid_cartesc_real_setup().

◆ atmos_grid_cartesc_real_fzxv

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fzxv

geopotential height [m] (wxv)

Definition at line 45 of file scale_atmos_grid_cartesC_real.F90.

45  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_FZXV(:,:,:)

Referenced by scale_atmos_grid_cartesc_metric::atmos_grid_cartesc_metric_rotcoef(), atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_finalize(), and atmos_grid_cartesc_real_setup().

◆ atmos_grid_cartesc_real_fzuv

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_fzuv

geopotential height [m] (wuv)

Definition at line 46 of file scale_atmos_grid_cartesC_real.F90.

46  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_FZUV(:,:,:)

Referenced by scale_atmos_grid_cartesc_metric::atmos_grid_cartesc_metric_rotcoef(), atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_finalize(), and atmos_grid_cartesc_real_setup().

◆ atmos_grid_cartesc_real_f2h

real(rp), dimension (:,:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_f2h

◆ atmos_grid_cartesc_real_lon

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lon

◆ atmos_grid_cartesc_real_lonuy

real(rp), dimension(:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lonuy

◆ atmos_grid_cartesc_real_lonxv

real(rp), dimension(:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lonxv

◆ atmos_grid_cartesc_real_lonuv

real(rp), dimension(:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lonuv

longitude at staggered point (uv) [rad,0-2pi]

Definition at line 52 of file scale_atmos_grid_cartesC_real.F90.

52  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_LONUV(:,:)

Referenced by atmos_grid_cartesc_real_calc_z(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), scale_comm_cartesc_nest::comm_cartesc_nest_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_lat

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lat

◆ atmos_grid_cartesc_real_latuy

real(rp), dimension(:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latuy

◆ atmos_grid_cartesc_real_latxv

real(rp), dimension(:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latxv

◆ atmos_grid_cartesc_real_latuv

real(rp), dimension(:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latuv

◆ atmos_grid_cartesc_real_dlon

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_dlon

delta longitude

Definition at line 57 of file scale_atmos_grid_cartesC_real.F90.

57  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_DLON (:,:)

Referenced by atmos_grid_cartesc_real_finalize(), and atmos_grid_cartesc_real_setup().

◆ atmos_grid_cartesc_real_dlat

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_dlat

delta latitude

Definition at line 58 of file scale_atmos_grid_cartesC_real.F90.

58  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_DLAT (:,:)

Referenced by atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and mod_cnvlanduse::cnvlanduse().

◆ atmos_grid_cartesc_real_z1

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_z1

◆ atmos_grid_cartesc_real_aspect_max

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_aspect_max

maximum aspect ratio of the grid cell

Definition at line 61 of file scale_atmos_grid_cartesC_real.F90.

61  real(RP), public :: ATMOS_GRID_CARTESC_REAL_ASPECT_MAX

Referenced by atmos_grid_cartesc_real_calc_z().

◆ atmos_grid_cartesc_real_aspect_min

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_aspect_min

minimum aspect ratio of the grid cell

Definition at line 62 of file scale_atmos_grid_cartesC_real.F90.

62  real(RP), public :: ATMOS_GRID_CARTESC_REAL_ASPECT_MIN

Referenced by atmos_grid_cartesc_real_calc_z().

◆ atmos_grid_cartesc_real_phi

real(rp), dimension (:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_phi

◆ atmos_grid_cartesc_real_area

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_area

◆ atmos_grid_cartesc_real_areazuy_x

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuy_x

◆ atmos_grid_cartesc_real_areazxv_y

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxv_y

◆ atmos_grid_cartesc_real_areawuy_x

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areawuy_x

virtical area (wuy, normal x) [m2]

Definition at line 69 of file scale_atmos_grid_cartesC_real.F90.

69  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAWUY_X(:,:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_areawxv_y

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areawxv_y

virtical area (wxv, normal y) [m2]

Definition at line 70 of file scale_atmos_grid_cartesC_real.F90.

70  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAWXV_Y(:,:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_areauy

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areauy

horizontal area ( uy, normal z) [m2]

Definition at line 71 of file scale_atmos_grid_cartesC_real.F90.

71  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAUY (:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), scale_file_history_cartesc::file_history_cartesc_truncate_3d(), and scale_monitor_cartesc::monitor_cartesc_setup().

◆ atmos_grid_cartesc_real_areazxy_x

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxy_x

virtical area (zxy, normal x) [m2]

Definition at line 72 of file scale_atmos_grid_cartesC_real.F90.

72  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAZXY_X(:,:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_areazuv_y

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuv_y

virtical area (zuv, normal y) [m2]

Definition at line 73 of file scale_atmos_grid_cartesC_real.F90.

73  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAZUV_Y(:,:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_areaxv

real(rp), dimension (:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areaxv

horizontal area ( xv, normal z) [m2]

Definition at line 74 of file scale_atmos_grid_cartesC_real.F90.

74  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAXV (:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), scale_file_history_cartesc::file_history_cartesc_truncate_3d(), and scale_monitor_cartesc::monitor_cartesc_setup().

◆ atmos_grid_cartesc_real_areazuv_x

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazuv_x

virtical area (zuv, normal x) [m2]

Definition at line 75 of file scale_atmos_grid_cartesC_real.F90.

75  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAZUV_X(:,:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_areazxy_y

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_areazxy_y

virtical area (zxy, normal y) [m2]

Definition at line 76 of file scale_atmos_grid_cartesC_real.F90.

76  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_AREAZXY_Y(:,:,:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

◆ atmos_grid_cartesc_real_totarea

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totarea

◆ atmos_grid_cartesc_real_totareauy

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareauy

total area (uy, local) [m2]

Definition at line 79 of file scale_atmos_grid_cartesC_real.F90.

79  real(RP), public :: ATMOS_GRID_CARTESC_REAL_TOTAREAUY

Referenced by atmos_grid_cartesc_real_calc_areavol(), and scale_monitor_cartesc::monitor_cartesc_setup().

◆ atmos_grid_cartesc_real_totareaxv

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareaxv

total area (xv, local) [m2]

Definition at line 80 of file scale_atmos_grid_cartesC_real.F90.

80  real(RP), public :: ATMOS_GRID_CARTESC_REAL_TOTAREAXV

Referenced by atmos_grid_cartesc_real_calc_areavol(), and scale_monitor_cartesc::monitor_cartesc_setup().

◆ atmos_grid_cartesc_real_totareazuy_x

real(rp), dimension(:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazuy_x

total area (zuy, normal x) [m2]

Definition at line 81 of file scale_atmos_grid_cartesC_real.F90.

81  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_TOTAREAZUY_X(:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), mod_atmos_bnd_driver::calc_mass(), and scale_monitor_cartesc::monitor_cartesc_setup().

◆ atmos_grid_cartesc_real_totareazxv_y

real(rp), dimension(:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totareazxv_y

total area (zxv, normal y) [m2]

Definition at line 82 of file scale_atmos_grid_cartesC_real.F90.

82  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_TOTAREAZXV_Y(:)

Referenced by atmos_grid_cartesc_real_calc_areavol(), atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), mod_atmos_bnd_driver::calc_mass(), and scale_monitor_cartesc::monitor_cartesc_setup().

◆ atmos_grid_cartesc_real_vol

real(rp), dimension (:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_vol

◆ atmos_grid_cartesc_real_volwxy

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_volwxy

◆ atmos_grid_cartesc_real_volzuy

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_volzuy

◆ atmos_grid_cartesc_real_volzxv

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_volzxv

◆ atmos_grid_cartesc_real_totvol

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvol

◆ atmos_grid_cartesc_real_totvolwxy

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvolwxy

◆ atmos_grid_cartesc_real_totvolzuy

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvolzuy

◆ atmos_grid_cartesc_real_totvolzxv

real(rp), public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_totvolzxv

◆ atmos_grid_cartesc_real_domain_catalogue

real(rp), dimension(:,:,:), allocatable, public scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_domain_catalogue

domain latlon catalogue [rad]

Definition at line 93 of file scale_atmos_grid_cartesC_real.F90.

93  real(RP), public, allocatable :: ATMOS_GRID_CARTESC_REAL_DOMAIN_CATALOGUE(:,:,:)

Referenced by atmos_grid_cartesc_real_finalize(), atmos_grid_cartesc_real_setup(), and scale_comm_cartesc_nest::comm_cartesc_nest_domain_shape().

scale_const::const_grav
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:49
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_interp_vert::interp_vert_finalize
subroutine, public interp_vert_finalize
Finalize.
Definition: scale_interp_vert.F90:686
scale_topography
module TOPOGRAPHY
Definition: scale_topography.F90:11
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:49
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_mapprojection
module Map projection
Definition: scale_mapprojection.F90:12
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_landuse::landuse_frac_land
real(rp), dimension(:,:), allocatable, public landuse_frac_land
land fraction
Definition: scale_landuse.F90:55
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_topography::topography_exist
logical, public topography_exist
topography exists?
Definition: scale_topography.F90:37
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:467
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:513
scale_topography::topography_zsfc
real(rp), dimension(:,:), allocatable, public topography_zsfc
absolute ground height [m]
Definition: scale_topography.F90:39
scale_prc::prc_nprocs
integer, public prc_nprocs
myrank in local communicator
Definition: scale_prc.F90:90
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:88
scale_comm_cartesc
module COMMUNICATION
Definition: scale_comm_cartesC.F90:11
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:53
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_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:43
scale_interp_vert
module INTERPOLATION vertical
Definition: scale_interp_vert.F90:11
scale_prc_cartesc::prc_twod
logical, public prc_twod
2D experiment
Definition: scale_prc_cartesC.F90:56
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11