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