SCALE-RM
scale_land_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 :: land_grid_setup
31 
32  !-----------------------------------------------------------------------------
33  !
34  !++ Public parameters & variables
35  !
36  real(RP), public, allocatable :: grid_lcz (:)
37  real(RP), public, allocatable :: grid_lfz (:)
38  real(RP), public, allocatable :: grid_lcdz (:)
39 
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private procedure
43  !
44  private :: land_grid_read
45  private :: land_grid_generate
46 
47  !-----------------------------------------------------------------------------
48  !
49  !++ Private parameters & variables
50  !
51  real(RP), private :: ldz(100)
52 
53  character(len=H_LONG), private :: land_grid_in_basename = ''
54  character(len=H_LONG), private :: land_grid_out_basename = ''
55 
56  !-----------------------------------------------------------------------------
57 contains
58  !-----------------------------------------------------------------------------
60  subroutine land_grid_setup
61  use scale_process, only: &
63  implicit none
64 
65  namelist / param_land_grid / &
66  land_grid_in_basename, &
67  land_grid_out_basename, &
68  ldz
69 
70  integer :: ierr
71  integer :: k
72 
73  !---------------------------------------------------------------------------
74 
75  if( io_l ) write(io_fid_log,*)
76  if( io_l ) write(io_fid_log,*) '++++++ Module[GRID] / Categ[LAND GRID] / Origin[SCALElib]'
77 
78  ldz(:) = 0.0_rp
79 
80  !--- read namelist
81  rewind(io_fid_conf)
82  read(io_fid_conf,nml=param_land_grid,iostat=ierr)
83  if( ierr < 0 ) then !--- missing
84  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
85  elseif( ierr > 0 ) then !--- fatal error
86  write(*,*) 'xxx Not appropriate names in namelist PARAM_LAND_GRID. Check!'
87  call prc_mpistop
88  endif
89  if( io_lnml ) write(io_fid_log,nml=param_land_grid)
90 
91  allocate( grid_lcz(lks :lke) )
92  allocate( grid_lfz(lks-1:lke) )
93  allocate( grid_lcdz(lks :lke) )
94 
95  if( io_l ) write(io_fid_log,*)
96  if( io_l ) write(io_fid_log,*) '*** Land grid information ***'
97 
98  if ( land_grid_in_basename /= '' ) then
99  call land_grid_read
100  else
101  if( io_l ) write(io_fid_log,*) '*** Not found input grid file. Grid position is calculated.'
102 
103  call land_grid_generate
104  endif
105 
106  if ( lke == lks ) then
107  if( io_l ) write(io_fid_log,*) '*** Single layer. LDZ = ', ldz(1)
108  else
109  if( io_l ) write(io_fid_log,'(1x,A)') &
110  '|====== Vertical Coordinate ======|'
111  if( io_l ) write(io_fid_log,'(1x,A)') &
112  '| k z zh dz k |'
113  if( io_l ) write(io_fid_log,'(1x,A)') &
114  '| [m] [m] [m] |'
115  k = lks-1
116  if( io_l ) write(io_fid_log,'(1x,A,F8.3,A,I4,A)') &
117  '| ',grid_lfz(k),' ',k,' | Atmosphere interface'
118  do k = lks, lke-1
119  if( io_l ) write(io_fid_log,'(1x,A,I4,F8.3,A,F8.3,A)') &
120  '|',k,grid_lcz(k),' ',grid_lcdz(k),' | '
121  if( io_l ) write(io_fid_log,'(1x,A,F8.3,A,I4,A)') &
122  '| ',grid_lfz(k),' |',k,' | '
123  enddo
124  k = lke
125  if( io_l ) write(io_fid_log,'(1x,A,I4,F8.3,A,F8.3,A)') &
126  '|',k,grid_lcz(k),' ',grid_lcdz(k),' | '
127  if( io_l ) write(io_fid_log,'(1x,A,F8.3,A,I4,A)') &
128  '| ',grid_lfz(k),' ',k,' | bedrock'
129  if( io_l ) write(io_fid_log,'(1x,A)') &
130  '|=================================|'
131  endif
132 
133  return
134  end subroutine land_grid_setup
135 
136  !-----------------------------------------------------------------------------
138  subroutine land_grid_read
139  use gtool_file, only: &
140  fileread
141  use scale_process, only: &
142  prc_myrank, &
144  use scale_grid, only: &
145  grid_cbfz, &
146  grid_cbfx, &
147  grid_cbfy
148  implicit none
149 
150  character(len=H_LONG) :: bname
151  real(RP) :: tmp_CBFZ(ka), tmp_CBFX(ia), tmp_CBFY(ja)
152  integer :: i, j, k
153  !---------------------------------------------------------------------------
154 
155  if( io_l ) write(io_fid_log,*)
156  if( io_l ) write(io_fid_log,*) '*** Input land grid file ***'
157 
158  write(bname,'(A,A,F15.3)') trim(land_grid_in_basename)
159 
160  call fileread( grid_lcz(:), bname, 'LCZ', 1, prc_myrank )
161  call fileread( grid_lcdz(:), bname, 'LCDZ', 1, prc_myrank )
162  call fileread( grid_lfz(:), bname, 'LFZ', 1, prc_myrank )
163 
164  call fileread( tmp_cbfz(:), bname, 'CBFZ', 1, prc_myrank )
165  call fileread( tmp_cbfy(:), bname, 'CBFX', 1, prc_myrank )
166  call fileread( tmp_cbfy(:), bname, 'CBFY', 1, prc_myrank )
167 
168  do i = 1, ia
169  if( tmp_cbfx(i) /= grid_cbfx(i) ) then
170  write( io_fid_log,'(A)') '*** Buffer layer in LAND_GRID_IN_BASENAME is different from GRID_IN_BASENAME ***'
171  call prc_mpistop
172  endif
173  enddo
174  do j = 1, ja
175  if( tmp_cbfy(j) /= grid_cbfy(j) ) then
176  write( io_fid_log,'(A)') '*** Buffer layer in LAND_GRID_IN_BASENAME is different from GRID_IN_BASENAME ***'
177  call prc_mpistop
178  endif
179  enddo
180  do k = 1, ka
181  if( tmp_cbfz(k) /= grid_cbfz(k) ) then
182  write( io_fid_log,'(A)') '*** Buffer layer in LAND_GRID_IN_BASENAME is different from GRID_IN_BASENAME ***'
183  call prc_mpistop
184  endif
185  enddo
186 
187  return
188  end subroutine land_grid_read
189 
190  !-----------------------------------------------------------------------------
192  subroutine land_grid_generate
193  implicit none
194 
195  integer :: k
196  !---------------------------------------------------------------------------
197 
198  do k = lks, lke
199  grid_lcdz(k) = ldz(k)
200  enddo
201 
202  grid_lfz(lks-1) = 0.0_rp
203 
204  do k = lks, lke
205  grid_lcz(k) = grid_lcdz(k) / 2.0_rp + grid_lfz(k-1)
206  grid_lfz(k) = grid_lcdz(k) + grid_lfz(k-1)
207  enddo
208 
209  return
210  end subroutine land_grid_generate
211 
212 end module scale_land_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 (cartesian) for land
real(rp), dimension(:), allocatable, public grid_lfz
face coordinate [m]: z, local=global
module grid index
integer, public ia
of x whole cells (local, with HALO)
integer, public ka
of z whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_cbfx
center buffer factor [0-1]: x
module PROCESS
subroutine, public land_grid_setup
Setup.
real(rp), dimension(:), allocatable, public grid_cbfz
center buffer factor [0-1]: z
integer, public prc_myrank
process num in local communicator
module GRID (cartesian)
module profiler
Definition: scale_prof.F90:10
real(rp), dimension(:), allocatable, public grid_lcdz
z-length of control volume [m]
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
module PRECISION
real(rp), dimension(:), allocatable, public grid_lcz
center coordinate [m]: z, local=global
real(rp), dimension(:), allocatable, public grid_cbfy
center buffer factor [0-1]: y
module land grid index
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
integer, public ja
of y whole cells (local, with HALO)