SCALE-RM
Functions/Subroutines | Variables
mod_cnvtopo Module Reference

module Convert topography More...

Functions/Subroutines

subroutine, public cnvtopo_setup
 Setup. More...
 
subroutine, public cnvtopo
 Driver. More...
 

Variables

logical, public cnvtopo_donothing
 
logical, public cnvtopo_usegtopo30 = .false.
 
logical, public cnvtopo_usegmted2010 = .false.
 
logical, public cnvtopo_usedem50m = .false.
 

Detailed Description

module Convert topography

Description
subroutines for preparing topography data (convert from external file)
Author
Team SCALE
NAMELIST
  • PARAM_CNVTOPO
    nametypedefault valuecomment
    CNVTOPO_NAME character(len=H_SHORT) 'NONE' keep backward compatibility
    CNVTOPO_USEGTOPO30 logical .false.
    CNVTOPO_USEGMTED2010 logical .false.
    CNVTOPO_USEDEM50M logical .false.
    CNVTOPO_UNITTILE_DDEG real(RP) dx for unit tile [deg]
    CNVTOPO_OVERSAMPLING_FACTOR real(RP) 2.0_RP factor of min. dx against the unit tile
    CNVTOPO_SMOOTH_MAXSLOPE real(RP)
    CNVTOPO_SMOOTH_MAXSLOPE_BND real(RP)
    CNVTOPO_SMOOTH_LOCAL logical .false.
    CNVTOPO_SMOOTH_ITELIM integer 1000
    CNVTOPO_SMOOTH_TYPE character(len=H_SHORT) 'LAPLACIAN'
    CNVTOPO_COPY_PARENT logical .false.

  • PARAM_CNVTOPO_GTOPO30
    nametypedefault valuecomment
    GTOPO30_IN_CATALOGUE character(len=H_LONG) '' metadata files for GTOPO30
    GTOPO30_IN_DIR character(len=H_LONG) '' directory contains GTOPO30 files (GrADS format)

  • PARAM_CNVTOPO_DEM50M
    nametypedefault valuecomment
    DEM50M_IN_CATALOGUE character(len=H_LONG) '' metadata files for DEM50M
    DEM50M_IN_DIR character(len=H_LONG) '' directory contains DEM50M files (GrADS format)

History Output
No history output

Function/Subroutine Documentation

◆ cnvtopo_setup()

subroutine, public mod_cnvtopo::cnvtopo_setup ( )

Setup.

Definition at line 68 of file mod_cnvtopo.f90.

References cnvtopo_donothing, cnvtopo_usedem50m, cnvtopo_usegmted2010, cnvtopo_usegtopo30, scale_const::const_d2r, scale_const::const_huge, scale_grid::dx, scale_grid::dy, scale_grid::grid_cdz, scale_grid::grid_fdx, scale_grid::grid_fdy, scale_grid_index::ie, scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_l, scale_stdio::io_lnml, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::ks, scale_process::prc_mpistop(), scale_grid_real::real_dlat, and scale_grid_real::real_dlon.

Referenced by mod_convert::convert_setup().

68  use scale_process, only: &
70  use scale_const, only: &
71  d2r => const_d2r, &
72  huge => const_huge
73  use scale_comm, only: &
74  comm_horizontal_min
75  use scale_grid, only: &
76  dx, &
77  dy, &
78  grid_cdz, &
79  grid_fdx, &
80  grid_fdy
81  use scale_grid_real, only: &
82  real_dlat, &
83  real_dlon
84  implicit none
85 
86  character(len=H_SHORT) :: cnvtopo_name = 'NONE' ! keep backward compatibility
87 
88  namelist / param_cnvtopo / &
89  cnvtopo_name, &
90  cnvtopo_usegtopo30, &
91  cnvtopo_usegmted2010, &
92  cnvtopo_usedem50m, &
93  cnvtopo_unittile_ddeg, &
94  cnvtopo_oversampling_factor, &
95  cnvtopo_smooth_maxslope, &
96  cnvtopo_smooth_maxslope_bnd, &
97  cnvtopo_smooth_local, &
98  cnvtopo_smooth_itelim, &
99  cnvtopo_smooth_type, &
100  cnvtopo_copy_parent
101 
102  real(RP) :: minslope(ia,ja)
103  real(RP) :: dxl(ia-1)
104  real(RP) :: dyl(ja-1)
105  real(RP) :: dzdx, dzdy
106 
107  real(RP) :: drad(ia,ja)
108  real(RP) :: drad_min
109 
110  integer :: ierr
111  integer :: k, i, j
112  !---------------------------------------------------------------------------
113 
114  if( io_l ) write(io_fid_log,*)
115  if( io_l ) write(io_fid_log,*) '++++++ Module[convert topo] / Categ[preprocess] / Origin[SCALE-RM]'
116 
117  if ( cnvtopo_smooth_local ) then
118  dxl(:) = dx
119  dyl(:) = dy
120  else
121  dxl(:) = grid_fdx(:)
122  dyl(:) = grid_fdy(:)
123  endif
124 
125  minslope(:,:) = huge
126 
127  j = js-1
128  i = is-1
129  do k = ks, ke
130  dzdx = atan2( 2.5_rp * grid_cdz(k), dxl(i) ) / d2r
131  dzdy = atan2( 2.5_rp * grid_cdz(k), dyl(j) ) / d2r
132  minslope(is,js) = min( minslope(is,js), dzdx, dzdy )
133  enddo
134 
135  j = js-1
136  do i = is, ie
137  do k = ks, ke
138  dzdx = atan2( 2.5_rp * grid_cdz(k), dxl(i) ) / d2r
139  dzdy = atan2( 2.5_rp * grid_cdz(k), dyl(j) ) / d2r
140  minslope(i,js) = min( minslope(i,js), dzdx, dzdy )
141  enddo
142  enddo
143 
144  i = is-1
145  do j = js, je
146  do k = ks, ke
147  dzdx = atan2( 2.5_rp * grid_cdz(k), dxl(i) ) / d2r
148  dzdy = atan2( 2.5_rp * grid_cdz(k), dyl(j) ) / d2r
149  minslope(is,j) = min( minslope(is,j), dzdx, dzdy )
150  enddo
151  enddo
152 
153  do j = js, je
154  do i = is, ie
155  do k = ks, ke
156  dzdx = atan2( 2.5_rp * grid_cdz(k), dxl(i) ) / d2r
157  dzdy = atan2( 2.5_rp * grid_cdz(k), dyl(j) ) / d2r
158  minslope(i,j) = min( minslope(i,j), dzdx, dzdy )
159  enddo
160  enddo
161  enddo
162 
163  call comm_horizontal_min( cnvtopo_smooth_maxslope, minslope(:,:) )
164 
165  cnvtopo_smooth_maxslope_bnd = -1.0_rp
166 
167  !--- read namelist
168  rewind(io_fid_conf)
169  read(io_fid_conf,nml=param_cnvtopo,iostat=ierr)
170  if( ierr < 0 ) then !--- missing
171  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
172  elseif( ierr > 0 ) then !--- fatal error
173  write(*,*) 'xxx Not appropriate names in namelist PARAM_CNVTOPO. Check!'
174  call prc_mpistop
175  endif
176  if( io_lnml ) write(io_fid_log,nml=param_cnvtopo)
177 
178  select case(cnvtopo_name)
179  case('NONE')
180  ! do nothing
181  case('GTOPO30')
182  cnvtopo_usegtopo30 = .true.
183  cnvtopo_usegmted2010 = .false.
184  cnvtopo_usedem50m = .false.
185  case('GMTED2010')
186  cnvtopo_usegtopo30 = .false.
187  cnvtopo_usegmted2010 = .true.
188  cnvtopo_usedem50m = .false.
189  case('DEM50M')
190  cnvtopo_usegtopo30 = .false.
191  cnvtopo_usegmted2010 = .false.
192  cnvtopo_usedem50m = .true.
193  case('COMBINE')
194  cnvtopo_usegtopo30 = .true.
195  cnvtopo_usegmted2010 = .true.
196  cnvtopo_usedem50m = .true.
197  case default
198  write(*,*) ' xxx Unsupported TYPE:', trim(cnvtopo_name)
199  call prc_mpistop
200  endselect
201 
202  cnvtopo_donothing = .true.
203 
204  if ( cnvtopo_usegtopo30 ) then
205  cnvtopo_donothing = .false.
206  if( io_l ) write(io_fid_log,*) '*** Use GTOPO, global 30 arcsec. data'
207  if ( cnvtopo_usegmted2010 ) then
208  if( io_l ) write(io_fid_log,*) '*** Use GMTED2010, new global 5 arcsec. data'
209  if( io_l ) write(io_fid_log,*) '*** Overwrite Existing region'
210  endif
211  if ( cnvtopo_usedem50m ) then
212  if( io_l ) write(io_fid_log,*) '*** Use DEM 50m data for Japan region'
213  if( io_l ) write(io_fid_log,*) '*** Overwrite Japan region'
214  endif
215  elseif ( cnvtopo_usegmted2010 ) then
216  cnvtopo_donothing = .false.
217  if( io_l ) write(io_fid_log,*) '*** Use GMTED2010, new global 5 arcsec. data'
218  if ( cnvtopo_usedem50m ) then
219  if( io_l ) write(io_fid_log,*) '*** Use DEM 50m data for Japan region'
220  if( io_l ) write(io_fid_log,*) '*** Overwrite Japan region'
221  endif
222  elseif ( cnvtopo_usedem50m ) then
223  cnvtopo_donothing = .false.
224  if( io_l ) write(io_fid_log,*) '*** Use DEM 50m data, Japan region only'
225  endif
226 
227  if ( cnvtopo_smooth_maxslope_bnd < 0.0_rp ) then
228  cnvtopo_smooth_maxslope_bnd = cnvtopo_smooth_maxslope
229  endif
230 
231  if ( cnvtopo_donothing ) then
232  if( io_l ) write(io_fid_log,*) '*** Do nothing for landuse index'
233  else
234  drad(:,:) = min( real_dlat(:,:), real_dlon(:,:) )
235  call comm_horizontal_min( drad_min, drad(:,:) )
236 
237  if ( cnvtopo_unittile_ddeg > 0.0_rp ) then
238  cnvtopo_oversampling_factor = ( drad_min / d2r ) / cnvtopo_unittile_ddeg
239  endif
240  cnvtopo_oversampling_factor = max( 1.0_rp, cnvtopo_oversampling_factor )
241  cnvtopo_unittile_ddeg = ( drad_min / d2r ) / cnvtopo_oversampling_factor
242 
243  if( io_l ) write(io_fid_log,*) '*** The size of tile [deg] = ', cnvtopo_unittile_ddeg
244  if( io_l ) write(io_fid_log,*) '*** oversampling factor = ', cnvtopo_oversampling_factor
245  endif
246 
247  return
integer, public is
start point of inner domain: x, local
integer, public je
end point of inner domain: y, local
real(rp), public dy
length in the main region [m]: y
real(rp), public const_huge
huge number
Definition: scale_const.F90:38
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:), allocatable, public grid_fdy
y-length of grid(j+1) to grid(j) [m]
real(rp), public dx
length in the main region [m]: x
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
integer, public ke
end point of inner domain: z, local
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:35
integer, public ia
of x whole cells (local, with HALO)
module GRID (real space)
real(rp), dimension(:,:), allocatable, public real_dlon
delta longitude
module COMMUNICATION
Definition: scale_comm.F90:23
integer, public js
start point of inner domain: y, local
module PROCESS
real(rp), dimension(:,:), allocatable, public real_dlat
delta latitude
module CONSTANT
Definition: scale_const.F90:14
integer, public ks
start point of inner domain: z, local
module GRID (cartesian)
integer, public ie
end point of inner domain: x, local
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
real(rp), dimension(:), allocatable, public grid_cdz
z-length of control volume [m]
real(rp), dimension(:), allocatable, public grid_fdx
x-length of grid(i+1) to grid(i) [m]
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)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cnvtopo()

subroutine, public mod_cnvtopo::cnvtopo ( )

Driver.

Definition at line 253 of file mod_cnvtopo.f90.

References cnvtopo_donothing, cnvtopo_usedem50m, cnvtopo_usegmted2010, cnvtopo_usegtopo30, scale_const::const_d2r, scale_const::const_eps, scale_const::const_pi, scale_const::const_radius, mod_copytopo::copytopo(), scale_grid::dx, scale_grid::dy, scale_grid::grid_cbfx, scale_grid::grid_cbfy, scale_grid::grid_fdx, scale_grid::grid_fdy, scale_grid_index::ia, scale_grid_index::ie, scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_get_available_fid(), scale_stdio::io_l, scale_stdio::io_lnml, scale_grid_index::is, scale_grid_index::ja, scale_grid_index::je, scale_grid_index::js, scale_process::prc_mpistop(), scale_grid_real::real_laty, scale_grid_real::real_lonx, scale_rm_statistics::stat_detail(), scale_topography::topo_fillhalo(), scale_topography::topo_write(), and scale_topography::topo_zsfc.

Referenced by mod_convert::convert().

253  use scale_process, only: &
255  use scale_const, only: &
256  pi => const_pi
257  use scale_grid, only: &
258  cbfx => grid_cbfx, &
259  cbfy => grid_cbfy
260  use scale_topography, only: &
261  topo_fillhalo, &
262  topo_zsfc, &
263  topo_write
264  use mod_copytopo, only: &
265  copytopo
266  implicit none
267 
268  real(RP) :: zsfc(ia,ja,2)
269  real(RP) :: frac
270  integer :: i, j
271  !---------------------------------------------------------------------------
272 
273  if ( cnvtopo_donothing ) then
274  if( io_l ) write(io_fid_log,*)
275  if( io_l ) write(io_fid_log,*) '++++++ SKIP CONVERT TOPOGRAPHY DATA ++++++'
276  else
277  if( io_l ) write(io_fid_log,*)
278  if( io_l ) write(io_fid_log,*) '++++++ START CONVERT TOPOGRAPHY DATA ++++++'
279 
280  if ( cnvtopo_usegtopo30 ) then
281  call cnvtopo_gtopo30
282  endif
283 
284  if ( cnvtopo_usegmted2010 ) then
285  call cnvtopo_gmted2010
286  endif
287 
288  if ( cnvtopo_usedem50m ) then
289  call cnvtopo_dem50m
290  endif
291 
292  zsfc(:,:,1) = topo_zsfc(:,:)
293  call cnvtopo_smooth( zsfc(:,:,1), & ! (inout)
294  cnvtopo_smooth_maxslope ) ! (in)
295 
296  zsfc(:,:,2) = zsfc(:,:,1)
297  call cnvtopo_smooth( zsfc(:,:,2), & ! (inout)
298  cnvtopo_smooth_maxslope_bnd ) ! (in)
299 
300  do j = 1, ja
301  do i = 1, ia
302  frac = sin( 0.5_rp * pi * max( cbfx(i), cbfy(j) ) )
303 
304  topo_zsfc(i,j) = ( 1.0_rp-frac ) * zsfc(i,j,1) &
305  + ( frac ) * zsfc(i,j,2)
306  enddo
307  enddo
308 
309  call topo_fillhalo
310 
311  if( cnvtopo_copy_parent ) call copytopo( topo_zsfc )
312 
313  if( io_l ) write(io_fid_log,*) '++++++ END CONVERT TOPOGRAPHY DATA ++++++'
314 
315  ! output topography file
316  call topo_write
317  endif
318 
319  return
subroutine, public topo_write
Write topography.
subroutine, public topo_fillhalo(Zsfc)
HALO Communication.
subroutine, public prc_mpistop
Abort MPI.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module Copy topography
integer, public ia
of x whole cells (local, with HALO)
real(rp), dimension(:), allocatable, public grid_cbfx
center buffer factor [0-1]: x
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
module GRID (cartesian)
subroutine, public copytopo(topo_cd)
Setup and Main.
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
real(rp), dimension(:), allocatable, public grid_cbfy
center buffer factor [0-1]: y
module TOPOGRAPHY
real(rp), public const_pi
pi
Definition: scale_const.F90:34
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, public ja
of y whole cells (local, with HALO)
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ cnvtopo_donothing

logical, public mod_cnvtopo::cnvtopo_donothing

Definition at line 34 of file mod_cnvtopo.f90.

Referenced by cnvtopo(), and cnvtopo_setup().

34  logical, public :: cnvtopo_donothing

◆ cnvtopo_usegtopo30

logical, public mod_cnvtopo::cnvtopo_usegtopo30 = .false.

Definition at line 35 of file mod_cnvtopo.f90.

Referenced by cnvtopo(), and cnvtopo_setup().

35  logical, public :: cnvtopo_usegtopo30 = .false.

◆ cnvtopo_usegmted2010

logical, public mod_cnvtopo::cnvtopo_usegmted2010 = .false.

Definition at line 36 of file mod_cnvtopo.f90.

Referenced by cnvtopo(), and cnvtopo_setup().

36  logical, public :: cnvtopo_usegmted2010 = .false.

◆ cnvtopo_usedem50m

logical, public mod_cnvtopo::cnvtopo_usedem50m = .false.

Definition at line 37 of file mod_cnvtopo.f90.

Referenced by cnvtopo(), and cnvtopo_setup().

37  logical, public :: cnvtopo_usedem50m = .false.