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...
 
subroutine cnvtopo_hypdiff (Zsfc, nite)
 

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) 0.0_RP dx for unit tile [deg]
    CNVTOPO_OVERSAMPLING_FACTOR real(RP) 2.0_RP factor of min. dx against the unit tile
    CNVTOPO_SMOOTH_HYPDIFF_NITER integer 20
    CNVTOPO_SMOOTH_MAXSLOPE_RATIO real(RP) 1.0_RP ratio of DZDX, DZDY
    CNVTOPO_SMOOTH_MAXSLOPE real(RP) -1.0_RP [deg]
    CNVTOPO_SMOOTH_LOCAL logical .true.
    CNVTOPO_SMOOTH_ITELIM integer 10000
    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 71 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_fid_nml, scale_stdio::io_l, scale_stdio::io_nml, 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().

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

References cnvtopo_donothing, cnvtopo_hypdiff(), 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_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_fid_nml, scale_stdio::io_get_available_fid(), scale_stdio::io_l, scale_stdio::io_nml, 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().

257  use scale_process, only: &
259  use scale_topography, only: &
260  topo_fillhalo, &
261  topo_zsfc, &
262  topo_write
263  use mod_copytopo, only: &
264  copytopo
265  implicit none
266  !---------------------------------------------------------------------------
267 
268  if ( cnvtopo_donothing ) then
269  if( io_l ) write(io_fid_log,*)
270  if( io_l ) write(io_fid_log,*) '++++++ SKIP CONVERT TOPOGRAPHY DATA ++++++'
271  else
272  if( io_l ) write(io_fid_log,*)
273  if( io_l ) write(io_fid_log,*) '++++++ START CONVERT TOPOGRAPHY DATA ++++++'
274 
275  if ( cnvtopo_usegtopo30 ) then
276  call cnvtopo_gtopo30
277  endif
278 
279  if ( cnvtopo_usegmted2010 ) then
280  call cnvtopo_gmted2010
281  endif
282 
283  if ( cnvtopo_usedem50m ) then
284  call cnvtopo_dem50m
285  endif
286 
287  call cnvtopo_smooth( topo_zsfc(:,:) ) ! (inout)
288  call topo_fillhalo
289 
290  if( cnvtopo_copy_parent ) call copytopo( topo_zsfc )
291 
292  if( io_l ) write(io_fid_log,*) '++++++ END CONVERT TOPOGRAPHY DATA ++++++'
293 
294  ! output topography file
295  call topo_write
296  endif
297 
298  return
subroutine, public topo_write
Write topography.
subroutine, public topo_fillhalo(Zsfc)
HALO Communication.
subroutine, public prc_mpistop
Abort MPI.
module Copy topography
module PROCESS
subroutine, public copytopo(topo_cd)
Setup and Main.
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
module TOPOGRAPHY
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cnvtopo_hypdiff()

subroutine mod_cnvtopo::cnvtopo_hypdiff ( real(rp), dimension(ia,ja), intent(inout)  Zsfc,
integer, intent(in)  nite 
)

Definition at line 1301 of file mod_cnvtopo.f90.

References scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, and scale_topography::topo_fillhalo().

Referenced by cnvtopo().

1301  use scale_topography, only: &
1303  real(RP), intent(inout) :: Zsfc(IA,JA)
1304  integer, intent(in) :: nite
1305 
1306  real(RP), pointer :: p1(:,:)
1307  real(RP), pointer :: p2(:,:)
1308  real(RP), target :: work1(IA,JA)
1309  real(RP), target :: work2(IA,JA)
1310 
1311  integer :: i, j
1312  integer :: ite, n
1313 
1314  ! reduce grid-scale variation
1315  do ite = 1, nite
1316  call topo_fillhalo( zsfc )
1317  work2(:,:) = zsfc(:,:)
1318  p1 => work2
1319  p2 => work1
1320  do n = 1, 4 ! 8th derivative
1321 ! do n = 1, 2 ! 4th derivative
1322  do j = js, je
1323  do i = is, ie
1324  p2(i,j) = ( - p1(i+1,j) + p1(i,j)*2.0_rp - p1(i-1,j) &
1325  - p1(i,j+1) + p1(i,j)*2.0_rp - p1(i,j-1) ) / 8.0_rp
1326  end do
1327  end do
1328  call topo_fillhalo( p2 )
1329  if ( mod(n,2) == 0 ) then
1330  p1 => work2
1331  p2 => work1
1332  else
1333  p1 => work1
1334  p2 => work2
1335  end if
1336  end do
1337  do j = js, je
1338  do i = is, ie
1339  zsfc(i,j) = max( zsfc(i,j) - p1(i,j), 0.0_rp )
1340  end do
1341  end do
1342  end do
1343 
1344  return
subroutine, public topo_fillhalo(Zsfc)
HALO Communication.
module TOPOGRAPHY
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.