SCALE-RM
scale_urban_grid.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
12 !-------------------------------------------------------------------------------
14  !-----------------------------------------------------------------------------
15  !
16  !++ used modules
17  !
18  use scale_precision
19  use scale_stdio
20  use scale_prof
23  !-----------------------------------------------------------------------------
24  implicit none
25  private
26  !-----------------------------------------------------------------------------
27  !
28  !++ Public procedure
29  !
30  public :: urban_grid_setup
31 
32  !-----------------------------------------------------------------------------
33  !
34  !++ Public parameters & variables
35  !
36  real(RP), public, allocatable :: grid_ucz (:)
37  real(RP), public, allocatable :: grid_ufz (:)
38  real(RP), public, allocatable :: grid_ucdz (:)
39 
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private procedure
43  !
44  private :: urban_grid_read
45  private :: urban_grid_generate
46 
47  !-----------------------------------------------------------------------------
48  !
49  !++ Private parameters & variables
50  !
51  real(RP), private :: udz(200)
52 
53  character(len=H_LONG), private :: urban_grid_in_basename = ''
54  character(len=H_LONG), private :: urban_grid_out_basename = ''
55 
56  !-----------------------------------------------------------------------------
57 contains
58  !-----------------------------------------------------------------------------
60  subroutine urban_grid_setup
61  use scale_process, only: &
63  implicit none
64 
65  namelist / param_urban_grid / &
66  urban_grid_in_basename, &
67  urban_grid_out_basename, &
68  udz
69 
70  integer :: ierr
71  integer :: k
72  !---------------------------------------------------------------------------
73 
74  if( io_l ) write(io_fid_log,*)
75  if( io_l ) write(io_fid_log,*) '++++++ Module[GRID] / Categ[URBAN GRID] / Origin[SCALElib]'
76 
77  udz(:) = 0.0_rp
78 
79  !--- read namelist
80  rewind(io_fid_conf)
81  read(io_fid_conf,nml=param_urban_grid,iostat=ierr)
82  if( ierr < 0 ) then !--- missing
83  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
84  elseif( ierr > 0 ) then !--- fatal error
85  write(*,*) 'xxx Not appropriate names in namelist PARAM_URBAN_GRID. Check!'
86  call prc_mpistop
87  endif
88  if( io_lnml ) write(io_fid_log,nml=param_urban_grid)
89 
90  allocate( grid_ucz(uks :uke) )
91  allocate( grid_ufz(uks-1:uke) )
92  allocate( grid_ucdz(uks :uke) )
93 
94  if( io_l ) write(io_fid_log,*)
95  if( io_l ) write(io_fid_log,*) '*** Urban grid information ***'
96 
97  if ( urban_grid_in_basename /= '' ) then
98  call urban_grid_read
99  else
100  if( io_l ) write(io_fid_log,*) '*** Not found input grid file. Grid position is calculated.'
101 
102  call urban_grid_generate
103  endif
104 
105  if ( uke == uks ) then
106  if( io_l ) write(io_fid_log,*) '*** Single layer. LDZ = ', udz(1)
107  else
108  if( io_l ) write(io_fid_log,'(1x,A)') &
109  '|====== Vertical Coordinate ======|'
110  if( io_l ) write(io_fid_log,'(1x,A)') &
111  '| k z zh dz k |'
112  if( io_l ) write(io_fid_log,'(1x,A)') &
113  '| [m] [m] [m] |'
114  k = uks-1
115  if( io_l ) write(io_fid_log,'(1x,A,F8.3,A,I4,A)') &
116  '| ',grid_ufz(k),' ',k,' | Atmosphere interface'
117  do k = uks, uke-1
118  if( io_l ) write(io_fid_log,'(1x,A,I4,F8.3,A,F8.3,A)') &
119  '|',k,grid_ucz(k),' ',grid_ucdz(k),' | '
120  if( io_l ) write(io_fid_log,'(1x,A,F8.3,A,I4,A)') &
121  '| ',grid_ufz(k),' |',k,' | '
122  enddo
123  k = uke
124  if( io_l ) write(io_fid_log,'(1x,A,I4,F8.3,A,F8.3,A)') &
125  '|',k,grid_ucz(k),' ',grid_ucdz(k),' | '
126  if( io_l ) write(io_fid_log,'(1x,A,F8.3,A,I4,A)') &
127  '| ',grid_ufz(k),' ',k,' | bedrock'
128  if( io_l ) write(io_fid_log,'(1x,A)') &
129  '|=================================|'
130  endif
131 
132  return
133  end subroutine urban_grid_setup
134 
135  !-----------------------------------------------------------------------------
137  subroutine urban_grid_read
138  use gtool_file, only: &
139  fileread
140  use scale_process, only: &
141  prc_myrank
142  implicit none
143 
144  character(len=H_LONG) :: bname
145  !---------------------------------------------------------------------------
146 
147  if( io_l ) write(io_fid_log,*)
148  if( io_l ) write(io_fid_log,*) '*** Input urban grid file ***'
149 
150  write(bname,'(A,A,F15.3)') trim(urban_grid_in_basename)
151 
152  call fileread( grid_ucz(:), bname, 'UCZ', 1, prc_myrank )
153  call fileread( grid_ucdz(:), bname, 'UCDZ', 1, prc_myrank )
154  call fileread( grid_ufz(:), bname, 'UFZ', 1, prc_myrank )
155 
156  return
157  end subroutine urban_grid_read
158 
159  !-----------------------------------------------------------------------------
161  subroutine urban_grid_generate
162  implicit none
163 
164  integer :: k
165  !---------------------------------------------------------------------------
166 
167  do k = uks, uke
168  grid_ucdz(k) = udz(k)
169  enddo
170 
171  grid_ufz(uks-1) = 0.0_rp
172 
173  do k = uks, uke
174  grid_ucz(k) = grid_ucdz(k) / 2.0_rp + grid_ufz(k-1)
175  grid_ufz(k) = grid_ucdz(k) + grid_ufz(k-1)
176  enddo
177 
178  return
179  end subroutine urban_grid_generate
180 
181 end module scale_urban_grid
module GTOOL_FILE
Definition: gtool_file.f90:17
subroutine, public prc_mpistop
Abort MPI.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module STDIO
Definition: scale_stdio.F90:12
module grid index
real(rp), dimension(:), allocatable, public grid_ucdz
z-length of control volume [m]
subroutine, public urban_grid_setup
Setup.
module GRID (cartesian) for urban
real(rp), dimension(:), allocatable, public grid_ufz
face coordinate [m]: z, local=global
module PROCESS
real(rp), dimension(:), allocatable, public grid_ucz
center coordinate [m]: z, local=global
integer, public prc_myrank
process num in local communicator
module profiler
Definition: scale_prof.F90:10
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
module PRECISION
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
module urban grid index