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.
 
logical, public cnvtopo_useuserfile = .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.

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

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

  • PARAM_CNVTOPO_USERFILE
    nametypedefault valuecomment
    USERFILE_DLAT real(RP) -1.0_RP width of latitude tile [deg.]
    USERFILE_DLON real(RP) -1.0_RP width of longitude tile [deg.]
    USERFILE_IN_CATALOGUE character(len=H_LONG) '' catalogue file
    USERFILE_IN_DIR character(len=H_LONG) '.' directory contains data files (GrADS format)
    USERFILE_IN_FILENAME character(len=H_LONG) '' single data file (GrADS format)
    USERFILE_IN_DATATYPE character(len=H_LONG) 'REAL4' datatype (REAL4,REAL8,INT2)
    USERFILE_LATORDER_N2S logical .false. data of the latitude direction is stored in ordar of North->South?
    USERFILE_LAT_START real(RP) -90.0_RP (for single file) start latitude of domain in input data
    USERFILE_LAT_END real(RP) 90.0_RP (for single file) end latitude of domain in input data
    USERFILE_LON_START real(RP) 0.0_RP (for single file) start longitude of domain in input data
    USERFILE_LON_END real(RP) 360.0_RP (for single file) end longitude of domain in input data

History Output
No history output

Function/Subroutine Documentation

◆ cnvtopo_setup()

subroutine, public mod_cnvtopo::cnvtopo_setup ( )

Setup.

Definition at line 80 of file mod_cnvtopo.F90.

References scale_atmos_grid_cartesc::atmos_grid_cartesc_cdz, scale_atmos_grid_cartesc::atmos_grid_cartesc_fdx, scale_atmos_grid_cartesc::atmos_grid_cartesc_fdy, cnvtopo_donothing, cnvtopo_usedem50m, cnvtopo_usegmted2010, cnvtopo_usegtopo30, cnvtopo_useuserfile, scale_const::const_d2r, scale_const::const_huge, scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_io::io_fid_conf, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_atmos_grid_cartesc_index::ke, scale_atmos_grid_cartesc_index::ks, and scale_prc::prc_abort().

Referenced by mod_convert::convert_setup().

80  use scale_prc, only: &
81  prc_abort
82  use scale_const, only: &
83  d2r => const_d2r, &
84  huge => const_huge
85  use scale_statistics, only: &
86  statistics_horizontal_min
87  use scale_atmos_grid_cartesc, only: &
88  cdz => atmos_grid_cartesc_cdz, &
89  fdx => atmos_grid_cartesc_fdx, &
91  implicit none
92 
93  character(len=H_SHORT) :: cnvtopo_name = 'NONE' ! keep backward compatibility
94 
95  namelist / param_cnvtopo / &
96  cnvtopo_name, &
97  cnvtopo_usegtopo30, &
98 ! CNVTOPO_UseGMTED2010, &
99  cnvtopo_usedem50m, &
100  cnvtopo_useuserfile, &
101  cnvtopo_smooth_trim_ocean, &
102  cnvtopo_smooth_hypdiff_order, &
103  cnvtopo_smooth_hypdiff_niter, &
104  cnvtopo_smooth_maxslope_ratio, &
105  cnvtopo_smooth_maxslope, &
106  cnvtopo_smooth_local, &
107  cnvtopo_smooth_itelim, &
108  cnvtopo_smooth_type, &
109  cnvtopo_copy_parent, &
110  cnvtopo_interp_level
111 
112  real(RP) :: minslope(ia,ja)
113  real(RP) :: dxl(ia-1)
114  real(RP) :: dyl(ja-1)
115  real(RP) :: dzdx, dzdy
116 
117  integer :: ierr
118  integer :: k, i, j
119  !---------------------------------------------------------------------------
120 
121  log_newline
122  log_info("CNVTOPO_setup",*) 'Setup'
123 
124  dxl(:) = fdx(:)
125  dyl(:) = fdy(:)
126 
127  !--- read namelist
128  rewind(io_fid_conf)
129  read(io_fid_conf,nml=param_cnvtopo,iostat=ierr)
130  if( ierr < 0 ) then !--- missing
131  log_info("CNVTOPO_setup",*) 'Not found namelist. Default used.'
132  elseif( ierr > 0 ) then !--- fatal error
133  log_error("CNVTOPO_setup",*) 'Not appropriate names in namelist PARAM_CNVTOPO. Check!'
134  call prc_abort
135  endif
136  log_nml(param_cnvtopo)
137 
138  select case(cnvtopo_name)
139  case('NONE')
140  ! do nothing
141  case('GTOPO30')
142  cnvtopo_usegtopo30 = .true.
143  cnvtopo_usegmted2010 = .false.
144  cnvtopo_usedem50m = .false.
145  cnvtopo_useuserfile = .false.
146 !!$ case('GMTED2010')
147 !!$ CNVTOPO_UseGTOPO30 = .false.
148 !!$ CNVTOPO_UseGMTED2010 = .true.
149 !!$ CNVTOPO_UseDEM50M = .false.
150 !!$ CNVTOPO_UseUSERFILE = .false.
151  case('DEM50M')
152  cnvtopo_usegtopo30 = .false.
153  cnvtopo_usegmted2010 = .false.
154  cnvtopo_usedem50m = .true.
155  cnvtopo_useuserfile = .false.
156  case('COMBINE')
157  cnvtopo_usegtopo30 = .true.
158  cnvtopo_usegmted2010 = .true.
159  cnvtopo_usedem50m = .true.
160  cnvtopo_useuserfile = .false.
161  case('USERFILE')
162  ! You can use GTOPO30, GMTED2010, DEM50M and combine User-defined file as you like
163  cnvtopo_useuserfile = .true.
164  case default
165  log_error("CNVTOPO_setup",*) 'Unsupported TYPE: ', trim(cnvtopo_name)
166  call prc_abort
167  endselect
168 
169  cnvtopo_donothing = .true.
170 
171  if ( cnvtopo_usegtopo30 ) then
172  cnvtopo_donothing = .false.
173  log_info("CNVTOPO_setup",*) 'Use GTOPO, global 30 arcsec. data'
174  if ( cnvtopo_usegmted2010 ) then
175  log_info("CNVTOPO_setup",*) 'Use GMTED2010, new global 5 arcsec. data'
176  log_info("CNVTOPO_setup",*) 'Overwrite Existing region'
177  endif
178  if ( cnvtopo_usedem50m ) then
179  log_info("CNVTOPO_setup",*) 'Use DEM 50m data for Japan region'
180  log_info("CNVTOPO_setup",*) 'Overwrite Japan region'
181  endif
182  elseif ( cnvtopo_usegmted2010 ) then
183  cnvtopo_donothing = .false.
184  log_info("CNVTOPO_setup",*) 'Use GMTED2010, new global 5 arcsec. data'
185  if ( cnvtopo_usedem50m ) then
186  log_info("CNVTOPO_setup",*) 'Use DEM 50m data for Japan region'
187  log_info("CNVTOPO_setup",*) 'Overwrite Japan region'
188  endif
189  elseif ( cnvtopo_usedem50m ) then
190  cnvtopo_donothing = .false.
191  log_info("CNVTOPO_setup",*) 'Use DEM 50m data, Japan region only'
192  elseif ( cnvtopo_useuserfile ) then
193  cnvtopo_donothing = .false.
194  log_info("CNVTOPO_setup",*) 'Use user-defined file'
195  endif
196 
197  if ( cnvtopo_donothing ) then
198  log_info("CNVTOPO_setup",*) 'Do nothing for topography data'
199  endif
200 
201  if( cnvtopo_smooth_maxslope > 0.0_rp ) then
202 
203  cnvtopo_smooth_maxslope_limit = cnvtopo_smooth_maxslope
204 
205  else
206  minslope(:,:) = huge
207 
208  j = js-1
209  i = is-1
210  do k = ks, ke
211  dzdx = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dxl(i) ) / d2r
212  dzdy = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dyl(j) ) / d2r
213  minslope(is,js) = min( minslope(is,js), dzdx, dzdy )
214  enddo
215 
216  j = js-1
217  do i = is, ie
218  do k = ks, ke
219  dzdx = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dxl(i) ) / d2r
220  dzdy = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dyl(j) ) / d2r
221  minslope(i,js) = min( minslope(i,js), dzdx, dzdy )
222  enddo
223  enddo
224 
225  i = is-1
226  !$omp parallel do &
227  !$omp private(DZDX,DZDY)
228  do j = js, je
229  do k = ks, ke
230  dzdx = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dxl(i) ) / d2r
231  dzdy = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dyl(j) ) / d2r
232  minslope(is,j) = min( minslope(is,j), dzdx, dzdy )
233  enddo
234  enddo
235 
236  !$omp parallel do &
237  !$omp private(DZDX,DZDY)
238  do j = js, je
239  do i = is, ie
240  do k = ks, ke
241  dzdx = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dxl(i) ) / d2r
242  dzdy = atan2( cnvtopo_smooth_maxslope_ratio * cdz(k), dyl(j) ) / d2r
243  minslope(i,j) = min( minslope(i,j), dzdx, dzdy )
244  enddo
245  enddo
246  enddo
247 
248  call statistics_horizontal_min( ia, is, ie, ja, js, je, &
249  minslope(:,:), cnvtopo_smooth_maxslope_limit )
250  end if
251 
252  return
real(rp), public const_huge
huge number
Definition: scale_const.F90:35
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:55
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:32
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdy
y-length of grid(j+1) to grid(j) [m]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdx
x-length of grid(i+1) to grid(i) [m]
module PROCESS
Definition: scale_prc.F90:11
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdz
z-length of control volume [m]
module atmosphere / grid / cartesC
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
module Statistics
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 258 of file mod_cnvtopo.F90.

References scale_atmos_grid_cartesc::atmos_grid_cartesc_fdx, scale_atmos_grid_cartesc::atmos_grid_cartesc_fdy, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lat, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_latxv, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lon, scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_lonuy, cnvtopo_donothing, cnvtopo_usedem50m, cnvtopo_usegmted2010, cnvtopo_usegtopo30, cnvtopo_useuserfile, scale_const::const_d2r, scale_const::const_eps, scale_const::const_radius, scale_const::const_undef, mod_copytopo::copytopo(), scale_atmos_grid_cartesc::dx, scale_atmos_grid_cartesc::dy, scale_file_tiledata::file_tiledata_get_info(), scale_atmos_grid_cartesc_index::ia, scale_atmos_grid_cartesc_index::ie, scale_interp::interp_factor2d(), scale_interp::interp_interp2d(), scale_io::io_fid_conf, scale_atmos_grid_cartesc_index::is, scale_atmos_grid_cartesc_index::ja, scale_atmos_grid_cartesc_index::je, scale_atmos_grid_cartesc_index::js, scale_landuse::landuse_fact_ocean, scale_prc::prc_abort(), scale_topography::topo_fillhalo(), scale_topography::topo_write(), and scale_topography::topo_zsfc.

Referenced by mod_convert::convert().

258  use scale_const, only: &
259  undef => const_undef, &
260  d2r => const_d2r
261  use scale_prc, only: &
262  prc_abort
263  use scale_topography, only: &
264  topo_fillhalo, &
265  topo_zsfc, &
266  topo_write
267  use mod_copytopo, only: &
268  copytopo
269  use scale_atmos_grid_cartesc_real, only: &
272  implicit none
273 
274  integer :: i, j
275  !---------------------------------------------------------------------------
276 
277  if ( cnvtopo_donothing ) then
278  log_newline
279  log_progress(*) 'skip convert topography data'
280  else
281  log_newline
282  log_progress(*) 'start convert topography data'
283 
284  domain_lats = minval( latxv(:,:) )
285  domain_late = maxval( latxv(:,:) )
286  domain_lons = minval( lonuy(:,:) )
287  domain_lone = maxval( lonuy(:,:) )
288 
289  log_info("CNVTOPO",*) 'Domain Information'
290  log_info_cont(*) 'Domain (LAT) :', domain_lats/d2r, domain_late/d2r
291  log_info_cont(*) ' (LON) :', domain_lons/d2r, domain_lone/d2r
292 
293  !$omp parallel do
294 !OCL XFILL
295  do j = 1, ja
296  do i = 1, ia
297  topo_zsfc(i,j) = 0.0_rp
298  end do
299  end do
300 
301  if ( cnvtopo_usegtopo30 ) then
302  call cnvtopo_gtopo30( topo_zsfc(:,:) ) ! [INOUT]
303  endif
304 
305  if ( cnvtopo_usegmted2010 ) then
306  call cnvtopo_gmted2010( topo_zsfc(:,:) ) ! [INOUT]
307  endif
308 
309  if ( cnvtopo_usedem50m ) then
310  call cnvtopo_dem50m( topo_zsfc(:,:) ) ! [INOUT]
311  endif
312 
313  if ( cnvtopo_useuserfile ) then
314  call cnvtopo_userfile( topo_zsfc(:,:) ) ! [INOUT]
315  endif
316 
317  call cnvtopo_smooth( topo_zsfc(:,:) ) ! (inout)
318  call topo_fillhalo( fill_bnd=.true. )
319 
320  if( cnvtopo_copy_parent ) call copytopo( topo_zsfc )
321 
322  log_progress(*) 'end convert topography data'
323 
324  ! output topography file
325  call topo_write
326  endif
327 
328  return
subroutine, public topo_write
Write topography.
subroutine, public topo_fillhalo(Zsfc, FILL_BND)
HALO Communication.
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:32
module Copy topography
subroutine, public copytopo(TOPO_child)
Setup and Main.
real(rp), public const_undef
Definition: scale_const.F90:41
module PROCESS
Definition: scale_prc.F90:11
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuy
longitude at staggered point (uy) [rad,0-2pi]
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
module Atmosphere GRID CartesC Real(real space)
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
module TOPOGRAPHY
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latxv
latitude at staggered point (xv) [rad,-pi,pi]
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 35 of file mod_cnvtopo.F90.

Referenced by cnvtopo(), and cnvtopo_setup().

35  logical, public :: cnvtopo_donothing

◆ cnvtopo_usegtopo30

logical, public mod_cnvtopo::cnvtopo_usegtopo30 = .false.

Definition at line 36 of file mod_cnvtopo.F90.

Referenced by cnvtopo(), and cnvtopo_setup().

36  logical, public :: cnvtopo_usegtopo30 = .false.

◆ cnvtopo_usegmted2010

logical, public mod_cnvtopo::cnvtopo_usegmted2010 = .false.

Definition at line 37 of file mod_cnvtopo.F90.

Referenced by cnvtopo(), and cnvtopo_setup().

37  logical, public :: cnvtopo_usegmted2010 = .false.

◆ cnvtopo_usedem50m

logical, public mod_cnvtopo::cnvtopo_usedem50m = .false.

Definition at line 38 of file mod_cnvtopo.F90.

Referenced by cnvtopo(), and cnvtopo_setup().

38  logical, public :: cnvtopo_usedem50m = .false.

◆ cnvtopo_useuserfile

logical, public mod_cnvtopo::cnvtopo_useuserfile = .false.

Definition at line 39 of file mod_cnvtopo.F90.

Referenced by cnvtopo(), and cnvtopo_setup().

39  logical, public :: cnvtopo_useuserfile = .false.