SCALE-RM
mod_mktopo.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
13 !-------------------------------------------------------------------------------
14 module mod_mktopo
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use scale_precision
20  use scale_stdio
21  use scale_prof
23  use scale_tracer
24 
25  use scale_process, only: &
27  use scale_grid, only: &
28  cx => grid_cx, &
29  cy => grid_cy
30  use scale_topography, only: &
31  topo_zsfc
32  !-----------------------------------------------------------------------------
33  implicit none
34  private
35  !-----------------------------------------------------------------------------
36  !
37  !++ Public procedure
38  !
39  public :: mktopo_setup
40  public :: mktopo
41 
42  !-----------------------------------------------------------------------------
43  !
44  !++ Public parameters & variables
45  !
46  integer, public :: mktopo_type = -1
47  integer, public, parameter :: i_ignore = 0
48  integer, public, parameter :: i_flat = 1
49  integer, public, parameter :: i_bellshape = 2
50  integer, public, parameter :: i_schaer = 3
51 
52  !-----------------------------------------------------------------------------
53  !
54  !++ Private procedure
55  !
56  private :: mktopo_flat
57  private :: mktopo_bellshape
58  private :: mktopo_schaer
59 
60  !-----------------------------------------------------------------------------
61  !
62  !++ Private parameters & variables
63  !
64  !-----------------------------------------------------------------------------
65 contains
66 
67  !-----------------------------------------------------------------------------
69  subroutine mktopo_setup
70  implicit none
71 
72  character(len=H_SHORT) :: mktopo_name = 'NONE'
73 
74  namelist / param_mktopo / &
75  mktopo_name
76 
77  integer :: ierr
78  !---------------------------------------------------------------------------
79 
80  if( io_l ) write(io_fid_log,*)
81  if( io_l ) write(io_fid_log,*) '++++++ Module[make topo] / Categ[preprocess] / Origin[SCALE-RM]'
82 
83  !--- read namelist
84  rewind(io_fid_conf)
85  read(io_fid_conf,nml=param_mktopo,iostat=ierr)
86  if( ierr < 0 ) then !--- missing
87  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
88  elseif( ierr > 0 ) then !--- fatal error
89  write(*,*) 'xxx Not appropriate names in namelist PARAM_MKTOPO. Check!'
90  call prc_mpistop
91  endif
92  if( io_nml ) write(io_fid_nml,nml=param_mktopo)
93 
94  select case(mktopo_name)
95  case('NONE')
97  case('FLAT')
99  case('BELLSHAPE')
101  case('SCHAER')
103  case default
104  write(*,*) 'xxx Unsupported TYPE:', trim(mktopo_name)
105  call prc_mpistop
106  endselect
107 
108  return
109  end subroutine mktopo_setup
110 
111  !-----------------------------------------------------------------------------
113  subroutine mktopo
114  use scale_topography, only: &
115  topo_write
116  implicit none
117  !---------------------------------------------------------------------------
118 
119  if ( mktopo_type == i_ignore ) then
120  if( io_l ) write(io_fid_log,*)
121  if( io_l ) write(io_fid_log,*) '++++++ SKIP MAKING TOPOGRAPHY DATA ++++++'
122  else
123  if( io_l ) write(io_fid_log,*)
124  if( io_l ) write(io_fid_log,*) '++++++ START MAKING TOPOGRAPHY DATA ++++++'
125 
126  select case(mktopo_type)
127  case(i_flat)
128  call mktopo_flat
129 
130  case(i_bellshape)
131  call mktopo_bellshape
132 
133  case(i_schaer)
134  call mktopo_schaer
135 
136  case default
137  write(*,*) 'xxx Unsupported TYPE:', mktopo_type
138  call prc_mpistop
139  endselect
140 
141  if( io_l ) write(io_fid_log,*) '++++++ END MAKING TOPOGRAPHY DATA ++++++'
142 
143  ! output topography file
144  call topo_write
145  endif
146 
147  return
148  end subroutine mktopo
149 
150  !-----------------------------------------------------------------------------
152  subroutine mktopo_flat
153  implicit none
154 
155  ! flat mountain parameter
156  real(RP) :: flat_height = 100.0_rp ! height of mountain [m]
157 
158  namelist / param_mktopo_flat / &
159  flat_height
160 
161  integer :: ierr
162  integer :: i, j
163  !---------------------------------------------------------------------------
164 
165  if( io_l ) write(io_fid_log,*)
166  if( io_l ) write(io_fid_log,*) '++++++ Module[mktopo FLAT] / Categ[preprocess] / Origin[SCALE-RM]'
167 
168  !--- read namelist
169  rewind(io_fid_conf)
170  read(io_fid_conf,nml=param_mktopo_flat,iostat=ierr)
171  if( ierr < 0 ) then !--- missing
172  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
173  elseif( ierr > 0 ) then !--- fatal error
174  write(*,*) 'xxx Not appropriate names in namelist PARAM_MKTOPO_FLAT. Check!'
175  call prc_mpistop
176  endif
177  if( io_nml ) write(io_fid_nml,nml=param_mktopo_flat)
178 
179  do j = 1, ja
180  do i = 1, ia
181  topo_zsfc(i,j) = flat_height
182  enddo
183  enddo
184 
185  return
186  end subroutine mktopo_flat
187 
188  !-----------------------------------------------------------------------------
190  subroutine mktopo_bellshape
191  implicit none
192 
193  ! bell-shaped mountain parameter
194  logical :: bell_eachnode = .false. ! Arrange mountain at each node? [kg/kg]
195  real(RP) :: bell_cx = 2.e3_rp ! center location [m]: x
196  real(RP) :: bell_cy = 2.e3_rp ! center location [m]: y
197  real(RP) :: bell_rx = 2.e3_rp ! bubble radius [m]: x
198  real(RP) :: bell_ry = 2.e3_rp ! bubble radius [m]: y
199  real(RP) :: bell_height = 100.0_rp ! height of mountain [m]
200 
201  namelist / param_mktopo_bellshape / &
202  bell_eachnode, &
203  bell_cx, &
204  bell_cy, &
205  bell_rx, &
206  bell_ry, &
207  bell_height
208 
209  real(RP) :: cx_offset
210  real(RP) :: cy_offset
211  real(RP) :: dist
212 
213  integer :: ierr
214  integer :: i, j
215  !---------------------------------------------------------------------------
216 
217  if( io_l ) write(io_fid_log,*)
218  if( io_l ) write(io_fid_log,*) '++++++ Module[mktopo BELLSHAPE] / Categ[preprocess] / Origin[SCALE-RM]'
219 
220  !--- read namelist
221  rewind(io_fid_conf)
222  read(io_fid_conf,nml=param_mktopo_bellshape,iostat=ierr)
223  if( ierr < 0 ) then !--- missing
224  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
225  elseif( ierr > 0 ) then !--- fatal error
226  write(*,*) 'xxx Not appropriate names in namelist PARAM_MKTOPO_BELLSHAPE. Check!'
227  call prc_mpistop
228  endif
229  if( io_nml ) write(io_fid_nml,nml=param_mktopo_bellshape)
230 
231  if ( bell_eachnode ) then
232  cx_offset = cx(is)
233  cy_offset = cy(js)
234  else
235  cx_offset = 0.0_rp
236  cy_offset = 0.0_rp
237  endif
238 
239  ! make bell-shaped mountain
240  do j = 1, ja
241  do i = 1, ia
242 
243  dist = ( (cx(i)-cx_offset-bell_cx)/bell_rx )**2 &
244  + ( (cy(j)-cy_offset-bell_cy)/bell_ry )**2
245 
246  topo_zsfc(i,j) = bell_height / ( 1.0_rp + dist )
247 
248  enddo
249  enddo
250 
251  return
252  end subroutine mktopo_bellshape
253 
254  !-----------------------------------------------------------------------------
258  subroutine mktopo_schaer
259  use scale_const, only: &
260  pi => const_pi
261  implicit none
262 
263  ! Schaer-type mountain parameter
264  real(RP) :: schaer_cx = 25.e3_rp ! center location [m]: x
265  real(RP) :: schaer_rx = 5.e3_rp ! bubble radius [m]: x
266  real(RP) :: schaer_lambda = 4.e3_rp ! wavelength of wavelike perturbation [m]: x
267  real(RP) :: schaer_height = 250.0_rp ! height of mountain [m]
268  logical :: schaer_swapxy = .false.
269 
270  namelist / param_mktopo_schaer / &
271  schaer_cx, &
272  schaer_rx, &
273  schaer_lambda, &
274  schaer_height, &
275  schaer_swapxy
276 
277  real(RP) :: dist
278 
279  integer :: ierr
280  integer :: i, j
281  !---------------------------------------------------------------------------
282 
283  if( io_l ) write(io_fid_log,*)
284  if( io_l ) write(io_fid_log,*) '++++++ Module[mktopo SCHEAR] / Categ[preprocess] / Origin[SCALE-RM]'
285 
286  !--- read namelist
287  rewind(io_fid_conf)
288  read(io_fid_conf,nml=param_mktopo_schaer,iostat=ierr)
289  if( ierr < 0 ) then !--- missing
290  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
291  elseif( ierr > 0 ) then !--- fatal error
292  write(*,*) 'xxx Not appropriate names in namelist PARAM_MKTOPO_SCHAER. Check!'
293  call prc_mpistop
294  endif
295  if( io_nml ) write(io_fid_nml,nml=param_mktopo_schaer)
296 
297  ! make bell-shaped mountain
298  if ( .NOT. schaer_swapxy ) then
299  do j = 1, ja
300  do i = 1, ia
301 
302  dist = exp( -( (cx(i)-schaer_cx)/schaer_rx )**2 )
303 
304  topo_zsfc(i,j) = schaer_height * dist * ( cos( pi*(cx(i)-schaer_cx)/schaer_lambda ) )**2
305 
306  enddo
307  enddo
308  else
309  do j = 1, ja
310  do i = 1, ia
311 
312  dist = exp( -( (cy(j)-schaer_cx)/schaer_rx )**2 )
313 
314  topo_zsfc(i,j) = schaer_height * dist * ( cos( pi*(cy(j)-schaer_cx)/schaer_lambda ) )**2
315 
316  enddo
317  enddo
318  endif
319 
320  return
321  end subroutine mktopo_schaer
322 
323 end module mod_mktopo
subroutine, public mktopo
Driver.
Definition: mod_mktopo.f90:114
subroutine, public topo_write
Write topography.
integer, public is
start point of inner domain: x, local
integer, public mktopo_type
Definition: mod_mktopo.f90:46
subroutine, public prc_mpistop
Abort MPI.
subroutine, public mktopo_setup
Setup.
Definition: mod_mktopo.f90:70
integer, parameter, public i_flat
Definition: mod_mktopo.f90:48
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:61
module STDIO
Definition: scale_stdio.F90:12
integer, parameter, public i_ignore
Definition: mod_mktopo.f90:47
module grid index
logical, public io_nml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:62
module TRACER
integer, public ia
of whole cells: x, local, with HALO
integer, parameter, public i_schaer
Definition: mod_mktopo.f90:50
integer, public js
start point of inner domain: y, local
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:), allocatable, public grid_cx
center coordinate [m]: x, local
module GRID (cartesian)
module MKTOPO
Definition: mod_mktopo.f90:14
module profiler
Definition: scale_prof.F90:10
integer, parameter, public i_bellshape
Definition: mod_mktopo.f90:49
module PRECISION
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
module TOPOGRAPHY
real(rp), public const_pi
pi
Definition: scale_const.F90:34
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 io_fid_nml
Log file ID (only for output namelist)
Definition: scale_stdio.F90:57
real(rp), dimension(:), allocatable, public grid_cy
center coordinate [m]: y, local
integer, public ja
of whole cells: y, local, with HALO