SCALE-RM
mod_cnvtopo.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  use scale_prof
20  use scale_tracer
21  !-----------------------------------------------------------------------------
22  implicit none
23  private
24  !-----------------------------------------------------------------------------
25  !
26  !++ Public procedure
27  !
28  public :: cnvtopo_setup
29  public :: cnvtopo
30 
31  !-----------------------------------------------------------------------------
32  !
33  !++ Public parameters & variables
34  !
35  logical, public :: cnvtopo_donothing
36  logical, public :: cnvtopo_usegtopo30 = .false.
37  logical, public :: cnvtopo_usegmted2010 = .false.
38  logical, public :: cnvtopo_usedem50m = .false.
39  logical, public :: cnvtopo_useuserfile = .false.
40 
41  !-----------------------------------------------------------------------------
42  !
43  !++ Private procedure
44  !
45  private :: cnvtopo_gtopo30
46  private :: cnvtopo_gmted2010
47  private :: cnvtopo_dem50m
48  private :: cnvtopo_userfile
49  private :: cnvtopo_smooth
50 
51  !-----------------------------------------------------------------------------
52  !
53  !++ Private parameters & variables
54  !
55  character(len=H_SHORT), private :: cnvtopo_smooth_type = 'LAPLACIAN' ! smoothing type
56  ! 'OFF' Do not apply smoothing
57  ! 'LAPLACIAN' Laplacian filter
58  ! 'GAUSSIAN' Gaussian filter
59  integer, private :: cnvtopo_smooth_hypdiff_order = 4
60  integer, private :: cnvtopo_smooth_hypdiff_niter = 20
61  logical, private :: cnvtopo_smooth_local = .true.
62  integer, private :: cnvtopo_smooth_itelim = 10000
63  logical, private :: cnvtopo_smooth_trim_ocean = .true.
64  real(RP), private :: cnvtopo_smooth_maxslope_ratio = 5.0_rp ! ratio of DZDX, DZDY
65  real(RP), private :: cnvtopo_smooth_maxslope = -1.0_rp ! [deg]
66  real(RP), private :: cnvtopo_smooth_maxslope_limit
67 
68  logical, private :: cnvtopo_copy_parent = .false.
69 
70  integer, private :: cnvtopo_interp_level = 5
71 
72  real(RP), private :: domain_lats, domain_late
73  real(RP), private :: domain_lons, domain_lone
74 
75  !-----------------------------------------------------------------------------
76 contains
77  !-----------------------------------------------------------------------------
79  subroutine cnvtopo_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, &
98 ! CNVTOPO_UseGMTED2010, &
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
253  end subroutine cnvtopo_setup
254 
255  !-----------------------------------------------------------------------------
257  subroutine cnvtopo
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
329  end subroutine cnvtopo
330 
331  !-----------------------------------------------------------------------------
333  subroutine cnvtopo_gtopo30( TOPO_Zsfc )
334  use scale_prc, only: &
335  prc_abort
336  use scale_const, only: &
337  undef => const_undef, &
338  d2r => const_d2r
339  use scale_atmos_grid_cartesc_real, only: &
342  use scale_file_tiledata, only: &
344  file_tiledata_get_data
345  use scale_interp, only: &
346  interp_factor2d, &
348  implicit none
349  real(RP), intent(inout) :: TOPO_Zsfc(ia,ja)
350 
351  character(len=H_LONG) :: GTOPO30_IN_DIR = '.'
352  character(len=H_LONG) :: GTOPO30_IN_CATALOGUE = ''
353 
354  namelist / param_cnvtopo_gtopo30 / &
355  gtopo30_in_dir, &
356  gtopo30_in_catalogue
357 
358  ! GTOPO30 data
359  real(RP), parameter :: GTOPO30_DLAT = 30.0_rp / 60.0_rp / 60.0_rp ! 30 arc sec.
360  real(RP), parameter :: GTOPO30_DLON = 30.0_rp / 60.0_rp / 60.0_rp ! 30 arc sec.
361 
362  ! topo
363  real(RP) :: Zsfc(ia,ja)
364 
365  ! data catalogue list
366  integer, parameter :: TILE_nlim = 100
367  integer :: TILE_nmax
368  character(len=H_LONG) :: TILE_fname(tile_nlim)
369  logical :: TILE_hit (tile_nlim)
370  integer :: TILE_JS (tile_nlim)
371  integer :: TILE_JE (tile_nlim)
372  integer :: TILE_IS (tile_nlim)
373  integer :: TILE_IE (tile_nlim)
374  real(RP) :: TILE_DLAT, TILE_DLON
375 
376  real(RP), allocatable :: HEIGHT(:,:)
377  real(RP), allocatable :: LATH (:,:)
378  real(RP), allocatable :: LONH (:,:)
379  integer :: nLONH, nLATH
380 
381  integer :: GLOBAL_IA
382 
383  ! interpolation
384  integer, allocatable :: idx_i(:,:,:)
385  integer, allocatable :: idx_j(:,:,:)
386  real(RP), allocatable :: hfact(:,:,:)
387 
388  character(len=H_LONG) :: fname
389 
390  integer :: ish, ieh, jsh, jeh
391  integer :: ierr
392  integer :: i, j
393  !---------------------------------------------------------------------------
394 
395  !--- read namelist
396  rewind(io_fid_conf)
397  read(io_fid_conf,nml=param_cnvtopo_gtopo30,iostat=ierr)
398  if( ierr < 0 ) then !--- missing
399  log_info("CNVTOPO_GTOPO30",*) 'Not found namelist. Default used.'
400  elseif( ierr > 0 ) then !--- fatal error
401  log_error("CNVTOPO_GTOPO30",*) 'Not appropriate names in namelist PARAM_CNVTOPO_GTOPO30. Check!'
402  call prc_abort
403  endif
404  log_nml(param_cnvtopo_gtopo30)
405 
406 
407  tile_dlat = gtopo30_dlat * d2r
408  tile_dlon = gtopo30_dlon * d2r
409 
410  ! catalogue file
411  fname = trim(gtopo30_in_dir)//'/'//trim(gtopo30_in_catalogue)
412 
413  call file_tiledata_get_info( tile_nlim, & ! [IN]
414  tile_dlat, tile_dlon, & ! [IN]
415  domain_lats, domain_late, domain_lons, domain_lone, & ! [IN]
416  fname, & ! [IN]
417  global_ia, & ! [OUT]
418  tile_nmax, & ! [OUT]
419  tile_fname(:), tile_hit(:), & ! [OUT]
420  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [OUT]
421  nlath, nlonh, jsh, jeh, ish, ieh ) ! [OUT]
422 
423  allocate( height(nlonh,nlath) )
424  allocate( lath(nlonh,nlath) )
425  allocate( lonh(nlonh,nlath) )
426 
427  call file_tiledata_get_data( nlath, nlonh, & ! [IN]
428  gtopo30_in_dir, & ! [IN]
429  global_ia, & ! [IN]
430  tile_nmax, & ! [IN]
431  tile_dlat, tile_dlon, & ! [IN]
432  tile_fname(:), tile_hit(:), & ! [IN]
433  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [IN]
434  jsh, jeh, ish, ieh, & ! [IN]
435  "INT2", & ! [IN]
436  height(:,:), lath(:,:), lonh(:,:), & ! [OUT]
437  min_value = -9000.0_rp, yrevers = .true. ) ! [IN]
438 
439  ! interporation
440  allocate( idx_i(ia,ja,cnvtopo_interp_level) )
441  allocate( idx_j(ia,ja,cnvtopo_interp_level) )
442  allocate( hfact(ia,ja,cnvtopo_interp_level) )
443 
444  call interp_factor2d( cnvtopo_interp_level, & ! [IN]
445  nlonh, nlath, & ! [IN]
446  lonh(:,:), lath(:,:), & ! [IN]
447  ia, ja, & ! [IN]
448  lon(:,:), lat(:,:), & ! [IN]
449  idx_i(:,:,:), idx_j(:,:,:), & ! [OUT]
450  hfact(:,:,:) ) ! [OUT]
451 
452  call interp_interp2d( cnvtopo_interp_level, & ! [IN]
453  nlonh,nlath, & ! [IN]
454  ia, ja, & ! [IN]
455  idx_i(:,:,:), idx_j(:,:,:), & ! [IN]
456  hfact(:,:,:), & ! [IN]
457  height(:,:), & ! [IN]
458  zsfc(:,:) ) ! [OUT]
459 
460 
461  deallocate( height, lath, lonh )
462  deallocate( idx_j, idx_i, hfact )
463 
464  !$omp parallel do
465  do j = 1, ja
466  do i = 1, ia
467  if ( zsfc(i,j) /= undef ) topo_zsfc(i,j) = zsfc(i,j) ! replace data
468  end do
469  end do
470 
471  return
472  end subroutine cnvtopo_gtopo30
473 
474  !-----------------------------------------------------------------------------
476  subroutine cnvtopo_gmted2010( TOPO_Zsfc )
477  implicit none
478  real(RP), intent(inout) :: TOPO_Zsfc(ia,ja)
479  !---------------------------------------------------------------------------
480 
481  return
482  end subroutine cnvtopo_gmted2010
483 
484  !-----------------------------------------------------------------------------
486  subroutine cnvtopo_dem50m( TOPO_Zsfc )
487  use scale_prc, only: &
488  prc_abort
489  use scale_const, only: &
490  undef => const_undef, &
491  radius => const_radius, &
492  d2r => const_d2r
493  use scale_atmos_grid_cartesc, only: &
494  dx, &
495  dy
496  use scale_atmos_grid_cartesc_real, only: &
499  use scale_file_tiledata, only: &
501  file_tiledata_get_data
502  use scale_interp, only: &
503  interp_factor2d, &
505  implicit none
506  real(RP), intent(inout) :: TOPO_Zsfc(ia,ja)
507 
508  character(len=H_LONG) :: DEM50M_IN_DIR = '.'
509  character(len=H_LONG) :: DEM50M_IN_CATALOGUE = ''
510 
511  namelist / param_cnvtopo_dem50m / &
512  dem50m_in_dir, &
513  dem50m_in_catalogue
514 
515  real(RP), parameter :: DEM50M_DLAT = 5.0_rp / 60.0_rp / 200.0_rp ! 30 arc sec.
516  real(RP), parameter :: DEM50M_DLON = 7.5_rp / 60.0_rp / 200.0_rp ! 30 arc sec.
517 
518  ! topo
519  real(RP) :: Zsfc(ia,ja)
520 
521  ! data catalogue list
522  integer, parameter :: TILE_nlim = 1000
523  integer :: TILE_nmax
524  character(len=H_LONG) :: TILE_fname(tile_nlim)
525  logical :: TILE_hit (tile_nlim)
526  integer :: TILE_JS (tile_nlim)
527  integer :: TILE_JE (tile_nlim)
528  integer :: TILE_IS (tile_nlim)
529  integer :: TILE_IE (tile_nlim)
530  real(RP) :: TILE_DLAT, TILE_DLON
531 
532  real(RP), allocatable :: HEIGHT(:,:)
533  real(RP), allocatable :: LATH (:,:)
534  real(RP), allocatable :: LONH (:,:)
535  integer :: nLONH, nLATH
536 
537  integer :: GLOBAL_IA
538 
539  ! interpolation
540  integer, allocatable :: idx_i(:,:,:)
541  integer, allocatable :: idx_j(:,:,:)
542  real(RP), allocatable :: hfact(:,:,:)
543  real(RP) :: search_limit
544 
545  character(len=H_LONG) :: fname
546 
547  integer :: ish, ieh, jsh, jeh
548  integer :: ierr
549  integer :: i, j
550  !---------------------------------------------------------------------------
551 
552  !--- read namelist
553  !--- read namelist
554  rewind(io_fid_conf)
555  read(io_fid_conf,nml=param_cnvtopo_dem50m,iostat=ierr)
556  if( ierr < 0 ) then !--- missing
557  log_info("CNVTOPO_DEM50M",*) 'Not found namelist. Default used.'
558  elseif( ierr > 0 ) then !--- fatal error
559  log_error("CNVTOPO_DEM50M",*) 'Not appropriate names in namelist PARAM_CNVTOPO_DEM50M. Check!'
560  call prc_abort
561  endif
562  log_nml(param_cnvtopo_dem50m)
563 
564  tile_dlat = dem50m_dlat * d2r
565  tile_dlon = dem50m_dlon * d2r
566 
567  ! catalogue file
568  fname = trim(dem50m_in_dir)//'/'//trim(dem50m_in_catalogue)
569 
570  call file_tiledata_get_info( tile_nlim, & ! [IN]
571  tile_dlat, tile_dlon, & ! [IN]
572  domain_lats, domain_late, domain_lons, domain_lone, & ! [IN]
573  fname, & ! [IN]
574  global_ia, & ! [OUT]
575  tile_nmax, & ! [OUT]
576  tile_fname(:), tile_hit(:), & ! [OUT]
577  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [OUT]
578  nlath, nlonh, jsh, jeh, ish, ieh ) ! [OUT]
579 
580  if ( .not. any(tile_hit(1:tile_nmax) ) ) return
581 
582  allocate( height(nlonh,nlath) )
583  allocate( lath(nlonh,nlath) )
584  allocate( lonh(nlonh,nlath) )
585 
586  call file_tiledata_get_data( nlath, nlonh, & ! [IN]
587  dem50m_in_dir, & ! [IN]
588  global_ia, & ! [IN]
589  tile_nmax, & ! [IN]
590  tile_dlat, tile_dlon, & ! [IN]
591  tile_fname(:), tile_hit(:), & ! [IN]
592  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [IN]
593  jsh, jeh, ish, ieh, & ! [IN]
594  "REAL4", & ! [IN]
595  height(:,:), lath(:,:), lonh(:,:), & ! [OUT]
596  min_value = -900.0_rp ) ! [IN]
597 
598  ! interporation
599  allocate( idx_i(ia,ja,cnvtopo_interp_level) )
600  allocate( idx_j(ia,ja,cnvtopo_interp_level) )
601  allocate( hfact(ia,ja,cnvtopo_interp_level) )
602 
603  search_limit = max( sqrt(tile_dlon**2 + tile_dlat**2) * radius * 1.5_rp, sqrt(dx**2 + dy**2) )
604  call interp_factor2d( cnvtopo_interp_level, & ! [IN]
605  nlonh, nlath, & ! [IN]
606  lonh(:,:), lath(:,:), & ! [IN]
607  ia, ja, & ! [IN]
608  lon(:,:), lat(:,:), & ! [IN]
609  idx_i(:,:,:), idx_j(:,:,:), & ! [OUT]
610  hfact(:,:,:), & ! [OUT]
611  latlon_structure = .true., & ! [OUT]
612  search_limit = search_limit ) ! [IN]
613 
614  call interp_interp2d( cnvtopo_interp_level, & ! [IN]
615  nlonh,nlath, & ! [IN]
616  ia, ja, & ! [IN]
617  idx_i(:,:,:), idx_j(:,:,:), & ! [IN]
618  hfact(:,:,:), & ! [IN]
619  height(:,:), & ! [IN]
620  zsfc(:,:) ) ! [OUT]
621 
622 
623  deallocate( height, lath, lonh )
624  deallocate( idx_j, idx_i, hfact )
625 
626  !$omp parallel do
627  do j = 1, ja
628  do i = 1, ia
629  if ( zsfc(i,j) /= undef ) topo_zsfc(i,j) = zsfc(i,j) ! replace data
630  end do
631  end do
632 
633  return
634  end subroutine cnvtopo_dem50m
635 
636  !-----------------------------------------------------------------------------
638  subroutine cnvtopo_userfile( TOPO_Zsfc )
639  use scale_prc, only: &
640  prc_abort
641  use scale_const, only: &
642  undef => const_undef, &
643  radius => const_radius, &
644  d2r => const_d2r
645  use scale_atmos_grid_cartesc, only: &
646  dx, &
647  dy
648  use scale_atmos_grid_cartesc_real, only: &
651  use scale_file_tiledata, only: &
653  file_tiledata_get_data
654  use scale_interp, only: &
655  interp_factor2d, &
657  implicit none
658  real(RP), intent(inout) :: TOPO_Zsfc(ia,ja)
659 
660  real(RP) :: USERFILE_DLAT = -1.0_rp ! width of latitude tile [deg.]
661  real(RP) :: USERFILE_DLON = -1.0_rp ! width of longitude tile [deg.]
662  character(len=H_LONG) :: USERFILE_IN_DIR = '.' ! directory contains data files (GrADS format)
663  character(len=H_LONG) :: USERFILE_IN_CATALOGUE = '' ! catalogue file
664  character(len=H_LONG) :: USERFILE_IN_FILENAME = '' ! single data file (GrADS format)
665  character(len=H_LONG) :: USERFILE_IN_DATATYPE = 'REAL4' ! datatype (REAL4,REAL8,INT2)
666  logical :: USERFILE_LATORDER_N2S = .false. ! data of the latitude direction is stored in ordar of North->South?
667  real(RP) :: USERFILE_LAT_START = -90.0_rp ! (for single file) start latitude of domain in input data
668  real(RP) :: USERFILE_LAT_END = 90.0_rp ! (for single file) end latitude of domain in input data
669  real(RP) :: USERFILE_LON_START = 0.0_rp ! (for single file) start longitude of domain in input data
670  real(RP) :: USERFILE_LON_END = 360.0_rp ! (for single file) end longitude of domain in input data
671 
672  namelist / param_cnvtopo_userfile / &
673  userfile_dlat, &
674  userfile_dlon, &
675  userfile_in_catalogue, &
676  userfile_in_dir, &
677  userfile_in_filename, &
678  userfile_in_datatype, &
679  userfile_latorder_n2s, &
680  userfile_lat_start, &
681  userfile_lat_end, &
682  userfile_lon_start, &
683  userfile_lon_end
684 
685  ! topo
686  real(RP) :: Zsfc(ia,ja)
687 
688  ! data catalogue list
689  integer, parameter :: TILE_nlim = 1000
690  integer :: TILE_nmax
691  character(len=H_LONG) :: TILE_fname(tile_nlim)
692  logical :: TILE_hit (tile_nlim)
693  integer :: TILE_JS (tile_nlim)
694  integer :: TILE_JE (tile_nlim)
695  integer :: TILE_IS (tile_nlim)
696  integer :: TILE_IE (tile_nlim)
697  real(RP) :: TILE_DLAT, TILE_DLON
698 
699  real(RP), allocatable :: HEIGHT(:,:)
700  real(RP), allocatable :: LATH (:,:)
701  real(RP), allocatable :: LONH (:,:)
702  integer :: nLONH, nLATH
703 
704  integer :: GLOBAL_IA
705 
706  ! interpolation
707  integer, allocatable :: idx_i(:,:,:)
708  integer, allocatable :: idx_j(:,:,:)
709  real(RP), allocatable :: hfact(:,:,:)
710  real(RP) :: search_limit
711 
712  character(len=H_LONG) :: fname
713 
714  real(RP) :: LATS, LATE, LONS, LONE
715  logical :: yrevers
716 
717  integer :: ish, ieh, jsh, jeh
718  integer :: ierr
719  integer :: i, j
720  !---------------------------------------------------------------------------
721 
722  !--- read namelist
723 
724  !--- read namelist
725  rewind(io_fid_conf)
726  read(io_fid_conf,nml=param_cnvtopo_userfile,iostat=ierr)
727  if( ierr < 0 ) then !--- missing
728  log_info("CNVTOPO_USERFILE",*) 'Not found namelist. Default used.'
729  elseif( ierr > 0 ) then !--- fatal error
730  log_error("CNVTOPO_USERFILE",*) 'Not appropriate names in namelist PARAM_CNVTOPO_USERFILE. Check!'
731  call prc_abort
732  endif
733  log_nml(param_cnvtopo_userfile)
734 
735  if ( userfile_dlat <= 0.0_rp ) then
736  log_error("CNVTOPO_USERFILE",*) 'USERFILE_DLAT (width (deg.) of latitude tile) should be positive. Check! ', userfile_dlat
737  call prc_abort
738  endif
739 
740  if ( userfile_dlon <= 0.0_rp ) then
741  log_error("CNVTOPO_USERFILE",*) 'USERFILE_DLON (width (deg.) of longitude tile) should be positive. Check! ', userfile_dlon
742  call prc_abort
743  endif
744 
745  if ( userfile_in_catalogue == '' &
746  .AND. userfile_in_filename == '' ) then
747  log_error("CNVTOPO_USERFILE",*) 'Neither catalogue file nor single file specified. Check!'
748  call prc_abort
749  endif
750 
751  if ( userfile_latorder_n2s ) then
752  log_info("CNVTOPO_USERFILE",*) 'data ordar of the latitude direction : North -> South'
753  yrevers = .true.
754  else
755  log_info("CNVTOPO_USERFILE",*) 'data ordar of the latitude direction : South -> North'
756  yrevers = .false.
757  endif
758 
759 
760 
761  tile_dlat = userfile_dlat * d2r
762  tile_dlon = userfile_dlon * d2r
763 
764  if ( userfile_in_catalogue /= "" ) then
765  ! catalogue file
766  fname = trim(userfile_in_dir)//'/'//trim(userfile_in_catalogue)
767 
768  call file_tiledata_get_info( tile_nlim, & ! [IN]
769  tile_dlat, tile_dlon, & ! [IN]
770  domain_lats, domain_late, domain_lons, domain_lone, & ! [IN]
771  fname, & ! [IN]
772  global_ia, & ! [OUT]
773  tile_nmax, & ! [OUT]
774  tile_fname(:), tile_hit(:), & ! [OUT]
775  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [OUT]
776  nlath, nlonh, jsh, jeh, ish, ieh ) ! [OUT]
777  else
778  lats = userfile_lat_start * d2r
779  late = userfile_lat_end * d2r
780  lons = userfile_lon_start * d2r
781  lone = userfile_lon_end * d2r
782  call file_tiledata_get_info( tile_nlim, & ! [IN]
783  tile_dlat, tile_dlon, & ! [IN]
784  domain_lats, domain_late, domain_lons, domain_lone, & ! [IN]
785  '', & ! [IN]
786  global_ia, & ! [OUT]
787  tile_nmax, & ! [OUT]
788  tile_fname(:), tile_hit(:), & ! [OUT]
789  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [OUT]
790  nlath, nlonh, jsh, jeh, ish, ieh, & ! [OUT]
791  single_fname = userfile_in_filename, & ! [IN]
792  lats = lats, late = late, lons = lons, lone = lone ) ! [IN]
793  end if
794 
795  if ( .not. any(tile_hit(1:tile_nmax) ) ) return
796 
797  allocate( height(nlonh,nlath) )
798  allocate( lath(nlonh,nlath) )
799  allocate( lonh(nlonh,nlath) )
800 
801  call file_tiledata_get_data( nlath, nlonh, & ! [IN]
802  userfile_in_dir, & ! [IN]
803  global_ia, & ! [IN]
804  tile_nmax, & ! [IN]
805  tile_dlat, tile_dlon, & ! [IN]
806  tile_fname(:), tile_hit(:), & ! [IN]
807  tile_js(:), tile_je(:), tile_is(:), tile_ie(:), & ! [IN]
808  jsh, jeh, ish, ieh, & ! [IN]
809  userfile_in_datatype, & ! [IN]
810  height(:,:), lath(:,:), lonh(:,:), & ! [OUT]
811  min_value = 0.0_rp, yrevers = yrevers ) ! [IN]
812 
813  ! interporation
814  allocate( idx_i(ia,ja,cnvtopo_interp_level) )
815  allocate( idx_j(ia,ja,cnvtopo_interp_level) )
816  allocate( hfact(ia,ja,cnvtopo_interp_level) )
817 
818  search_limit = max( sqrt(tile_dlon**2 + tile_dlat**2) * radius * 1.5_rp, sqrt(dx**2 + dy**2) )
819  call interp_factor2d( cnvtopo_interp_level, & ! [IN]
820  nlonh, nlath, & ! [IN]
821  lonh(:,:), lath(:,:), & ! [IN]
822  ia, ja, & ! [IN]
823  lon(:,:), lat(:,:), & ! [IN]
824  idx_i(:,:,:), idx_j(:,:,:), & ! [OUT]
825  hfact(:,:,:), & ! [OUT]
826  latlon_structure = .true., & ! [OUT]
827  search_limit = search_limit ) ! [IN]
828 
829  call interp_interp2d( cnvtopo_interp_level, & ! [IN]
830  nlonh,nlath, & ! [IN]
831  ia, ja, & ! [IN]
832  idx_i(:,:,:), idx_j(:,:,:), & ! [IN]
833  hfact(:,:,:), & ! [IN]
834  height(:,:), & ! [IN]
835  zsfc(:,:) ) ! [OUT]
836 
837  deallocate( height, lath, lonh )
838  deallocate( idx_j, idx_i, hfact )
839 
840  !$omp parallel do
841  do j = 1, ja
842  do i = 1, ia
843  if ( zsfc(i,j) /= undef ) topo_zsfc(i,j) = zsfc(i,j) ! replace data
844  end do
845  end do
846 
847  return
848  end subroutine cnvtopo_userfile
849 
850  !-----------------------------------------------------------------------------
852  subroutine cnvtopo_smooth( &
853  Zsfc )
854  use scale_const, only: &
855  eps => const_eps, &
856  d2r => const_d2r
857  use scale_prc, only: &
858  prc_abort
859  use scale_atmos_grid_cartesc, only: &
860  fdx => atmos_grid_cartesc_fdx, &
862  use scale_statistics, only: &
863  statistics_detail, &
864  statistics_horizontal_max
865  use scale_topography, only: &
867  use scale_filter, only: &
868  filter_hyperdiff
869  use scale_landuse, only: &
871  implicit none
872 
873  real(RP), intent(inout) :: Zsfc(ia,ja)
874 
875  real(RP) :: DZsfc_DXY(ia,ja,2) ! d(Zsfc)/dx at u-position and d(Zsfc)/dy at v-position
876 
877  real(RP) :: DXL(ia-1)
878  real(RP) :: DYL(ja-1)
879 
880  real(RP) :: FLX_X(ia,ja)
881  real(RP) :: FLX_Y(ia,ja)
882 
883  real(RP) :: slope(ia,ja)
884  real(RP) :: maxslope
885  real(RP), pointer :: TOPO_sign(:,:)
886  real(RP) :: flag, ocean_flag
887 
888  character(len=8), parameter :: varname(2) = (/ "DZsfc_DX", "DZsfc_DY" /)
889 
890 
891  integer :: ite
892  integer :: i, j
893  !---------------------------------------------------------------------------
894 
895  if ( cnvtopo_smooth_type == 'OFF' ) then
896  log_newline
897  log_info("CNVTOPO_smooth",*) 'Do not apply smoothing.'
898 
899  return
900  else
901  log_newline
902  log_info("CNVTOPO_smooth",*) 'Apply smoothing.'
903  log_info_cont(*) 'Slope limit = ', cnvtopo_smooth_maxslope_limit
904  log_info_cont(*) 'Smoothing type = ', cnvtopo_smooth_type
905  log_info_cont(*) 'Smoothing locally = ', cnvtopo_smooth_local
906  log_newline
907  endif
908 
909  dxl(:) = fdx(:)
910  dyl(:) = fdy(:)
911 
912  if ( cnvtopo_smooth_trim_ocean ) then
913  allocate( topo_sign(ia,ja) )
914  !$omp parallel do &
915  !$omp private(ocean_flag)
916  do j = 1, ja
917  do i = 1, ia
918  ocean_flag = ( 0.5_rp + sign( 0.5_rp, landuse_fact_ocean(i,j) - 1.0_rp + eps ) ) & ! fact_ocean==1
919  * ( 0.5_rp + sign( 0.5_rp, eps - abs(zsfc(i,j)) ) ) ! |Zsfc| < EPS
920  topo_sign(i,j) = sign( 1.0_rp, zsfc(i,j) ) * ( 1.0_rp - ocean_flag )
921  end do
922  end do
923  else
924  topo_sign => null()
925  end if
926 
927  ! digital filter
928  do ite = 1, cnvtopo_smooth_itelim+1
929  log_progress(*) 'smoothing itelation : ', ite
930 
931  call topo_fillhalo( zsfc=zsfc(:,:), fill_bnd=.true. )
932 
933  !$omp parallel do
934  do j = 1, ja
935  do i = 1, ia-1
936  dzsfc_dxy(i,j,1) = atan2( ( zsfc(i+1,j)-zsfc(i,j) ), dxl(i) ) / d2r
937  enddo
938  enddo
939  dzsfc_dxy(ia,:,1) = 0.0_rp
940  !$omp parallel do
941  do j = 1, ja-1
942  do i = 1, ia
943  dzsfc_dxy(i,j,2) = atan2( ( zsfc(i,j+1)-zsfc(i,j) ), dyl(j) ) / d2r
944  enddo
945  enddo
946  dzsfc_dxy(:,ja,2) = 0.0_rp
947 
948  slope(:,:) = max( abs(dzsfc_dxy(:,:,1)), abs(dzsfc_dxy(:,:,2)) )
949  call statistics_horizontal_max( ia, is, ie, ja, js, je, &
950  slope(:,:), maxslope )
951 
952  log_progress(*) 'maximum slope [deg] : ', maxslope
953 
954  if( maxslope < cnvtopo_smooth_maxslope_limit ) exit
955 
956  call statistics_detail( ia, is, ie, ja, js, je, 2, &
957  varname(:), dzsfc_dxy(:,:,:) )
958 
959  select case( cnvtopo_smooth_type )
960  case( 'GAUSSIAN' )
961 
962  ! 3 by 3 gaussian filter
963  !$omp parallel do
964  do j = js, je
965  do i = is, ie
966  zsfc(i,j) = ( 0.2500_rp * zsfc(i ,j ) &
967  + 0.1250_rp * zsfc(i-1,j ) &
968  + 0.1250_rp * zsfc(i+1,j ) &
969  + 0.1250_rp * zsfc(i ,j-1) &
970  + 0.1250_rp * zsfc(i ,j+1) &
971  + 0.0625_rp * zsfc(i-1,j-1) &
972  + 0.0625_rp * zsfc(i+1,j-1) &
973  + 0.0625_rp * zsfc(i-1,j+1) &
974  + 0.0625_rp * zsfc(i+1,j+1) )
975  enddo
976  enddo
977 
978  case( 'LAPLACIAN' )
979 
980  !$omp parallel do
981  do j = js , je
982  do i = is-1, ie
983  flx_x(i,j) = zsfc(i+1,j) - zsfc(i,j)
984 ! FLX_TMP(i,j) = Zsfc(i+1,j) - Zsfc(i,j)
985  enddo
986  enddo
987 !!$ call TOPO_fillhalo( FLX_TMP )
988 !!$ do j = JS , JE
989 !!$ do i = IS-1, IE
990 !!$ FLX_X(i,j) = - ( FLX_TMP(i+1,j) - FLX_TMP(i,j) )
991 !!$ enddo
992 !!$ enddo
993 
994  !$omp parallel do
995  do j = js-1, je
996  do i = is , ie
997  flx_y(i,j) = zsfc(i,j+1) - zsfc(i,j)
998 ! FLX_TMP(i,j) = Zsfc(i,j+1) - Zsfc(i,j)
999  enddo
1000  enddo
1001 !!$ call TOPO_fillhalo( FLX_TMP )
1002 !!$ do j = JS-1, JE
1003 !!$ do i = IS , IE
1004 !!$ FLX_Y(i,j) = - ( FLX_TMP(i,j+1) - FLX_TMP(i,j) )
1005 !!$ enddo
1006 !!$ enddo
1007 
1008 
1009  if ( cnvtopo_smooth_local ) then
1010  !$omp parallel do &
1011  !$omp private(flag)
1012  do j = js , je
1013  do i = is-1, ie
1014  flag = 0.5_rp &
1015  + sign(0.5_rp, max( abs(dzsfc_dxy(i+1,j ,1)), &
1016  abs(dzsfc_dxy(i ,j ,1)), &
1017  abs(dzsfc_dxy(i-1,j ,1)), &
1018  abs(dzsfc_dxy(i+1,j ,2)), &
1019  abs(dzsfc_dxy(i+1,j-1,2)), &
1020  abs(dzsfc_dxy(i ,j ,2)), &
1021  abs(dzsfc_dxy(i ,j-1,2)) &
1022  ) - cnvtopo_smooth_maxslope_limit )
1023  flx_x(i,j) = flx_x(i,j) * flag
1024  enddo
1025  enddo
1026  !$omp parallel do &
1027  !$omp private(flag)
1028  do j = js-1, je
1029  do i = is , ie
1030  flag = 0.5_rp &
1031  + sign(0.5_rp, max( abs(dzsfc_dxy(i ,j+1,2)), &
1032  abs(dzsfc_dxy(i ,j ,2)), &
1033  abs(dzsfc_dxy(i ,j-1,2)), &
1034  abs(dzsfc_dxy(i ,j+1,1)), &
1035  abs(dzsfc_dxy(i-1,j+1,1)), &
1036  abs(dzsfc_dxy(i ,j ,1)), &
1037  abs(dzsfc_dxy(i-1,j ,1)) &
1038  ) - cnvtopo_smooth_maxslope_limit )
1039  flx_y(i,j) = flx_y(i,j) * flag
1040  enddo
1041  enddo
1042  endif
1043 
1044  !$omp parallel do
1045  do j = js, je
1046  do i = is, ie
1047  zsfc(i,j) = zsfc(i,j) &
1048  + 0.1_rp * ( ( flx_x(i,j) - flx_x(i-1,j) ) &
1049  + ( flx_y(i,j) - flx_y(i,j-1) ) )
1050  enddo
1051  enddo
1052 
1053  case default
1054  log_error("CNVTOPO_smooth",*) 'Invalid smoothing type'
1055  call prc_abort
1056  end select
1057 
1058  if ( cnvtopo_smooth_trim_ocean ) then
1059  !$omp parallel do
1060  do j = js, je
1061  do i = is, ie
1062  zsfc(i,j) = sign( max( zsfc(i,j) * topo_sign(i,j), 0.0_rp ), topo_sign(i,j) )
1063  end do
1064  end do
1065  end if
1066 
1067  enddo
1068 
1069  if ( ite > cnvtopo_smooth_itelim ) then
1070  log_error("CNVTOPO_smooth",*) 'Smoothing did not converge until ', cnvtopo_smooth_itelim,' times of iteration.'
1071 
1072  log_error_cont(*) 'Please try different parameters of PARAM_CNVTOPO.'
1073  log_error_cont(*) '- Number limit of iteration (CNVTOPO_smooth_itelim) = ', cnvtopo_smooth_itelim
1074  log_error_cont(*) '- Maximum ratio of slope dZ/dX, dZ/dY (CNVTOPO_smooth_maxslope_ratio) = ', cnvtopo_smooth_maxslope_ratio
1075  log_error_cont(*) ' Or, Maximum of slope with degree (CNVTOPO_smooth_maxslope) = ', cnvtopo_smooth_maxslope
1076  log_error_cont(*) '- Smoothing type LAPLACIAN/GAUSSIAN/OFF (CNVTOPO_smooth_type) = ', trim(cnvtopo_smooth_type)
1077  log_error_cont(*) '- Number of using points for interpolation (CNVTOPO_interp_level) = ', cnvtopo_interp_level
1078  call prc_abort
1079  else
1080  log_newline
1081  log_info("CNVTOPO_smooth",*) 'smoothing complete.'
1082  endif
1083 
1084 
1085 
1086  if ( cnvtopo_smooth_hypdiff_niter > 0 ) then
1087 
1088  log_newline
1089  log_info("CNVTOPO_smooth",*) 'Apply hyperdiffusion.'
1090 
1091  call filter_hyperdiff( ia, is, ie, ja, js, je, &
1092  zsfc(:,:), &
1093  cnvtopo_smooth_hypdiff_order, cnvtopo_smooth_hypdiff_niter, &
1094  limiter_sign = topo_sign(:,:) )
1095 
1096  !$omp parallel do
1097  do j = 1, ja
1098  do i = 1, ia-1
1099  dzsfc_dxy(i,j,1) = atan2( ( zsfc(i+1,j)-zsfc(i,j) ), dxl(i) ) / d2r
1100  enddo
1101  enddo
1102  dzsfc_dxy(ia,:,1) = 0.0_rp
1103  !$omp parallel do
1104  do j = 1, ja-1
1105  do i = 1, ia
1106  dzsfc_dxy(i,j,2) = atan2( ( zsfc(i,j+1)-zsfc(i,j) ), dyl(j) ) / d2r
1107  enddo
1108  enddo
1109  dzsfc_dxy(:,ja,2) = 0.0_rp
1110 
1111  slope(:,:) = max( abs(dzsfc_dxy(:,:,1)), abs(dzsfc_dxy(:,:,2)) )
1112  call statistics_horizontal_max( ia, is, ie, ja, js, je, &
1113  slope(:,:), maxslope )
1114 
1115  log_info("CNVTOPO_smooth",*) 'maximum slope [deg] : ', maxslope
1116 
1117  end if
1118 
1119  call topo_fillhalo( zsfc=zsfc(:,:), fill_bnd=.true. )
1120 
1121  call statistics_detail( ia, is, ie, ja, js, je, 2, &
1122  varname(:), dzsfc_dxy(:,:,:) )
1123 
1124  log_newline
1125 
1126  return
1127  end subroutine cnvtopo_smooth
1128 
1129 end module mod_cnvtopo
subroutine, public topo_write
Write topography.
logical, public cnvtopo_useuserfile
Definition: mod_cnvtopo.F90:39
real(rp), public const_huge
huge number
Definition: scale_const.F90:35
subroutine, public topo_fillhalo(Zsfc, FILL_BND)
HALO Communication.
integer, public ia
of whole cells: x, local, with HALO
module Convert topography
Definition: mod_cnvtopo.F90:11
logical, public cnvtopo_usedem50m
Definition: mod_cnvtopo.F90:38
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
real(rp), public const_radius
radius of the planet [m]
Definition: scale_const.F90:44
module INTERPOLATION
integer, public ja
of whole cells: y, local, with HALO
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
module Copy topography
subroutine, public copytopo(TOPO_child)
Setup and Main.
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_real_lon
longitude [rad,0-2pi]
real(rp), public const_undef
Definition: scale_const.F90:41
integer, public is
start point of inner domain: x, local
logical, public cnvtopo_donothing
Definition: mod_cnvtopo.F90:35
integer, public ie
end point of inner domain: x, local
module TRACER
module LANDUSE
module FILTER
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdx
x-length of grid(i+1) to grid(i) [m]
module atmosphere / grid / cartesC index
integer, public ke
end point of inner domain: z, local
module file_tiledata
module PROCESS
Definition: scale_prc.F90:11
integer, public je
end point of inner domain: y, local
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdz
z-length of control volume [m]
real(rp), dimension(:,:), allocatable, public landuse_fact_ocean
ocean factor
module atmosphere / grid / cartesC
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuy
longitude at staggered point (uy) [rad,0-2pi]
subroutine, public cnvtopo_setup
Setup.
Definition: mod_cnvtopo.F90:80
subroutine, public interp_interp2d(npoints, IA_ref, JA_ref, IA, JA, idx_i, idx_j, hfact, val_ref, val)
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
module CONSTANT
Definition: scale_const.F90:11
integer, public js
start point of inner domain: y, local
subroutine, public cnvtopo
Driver.
logical, public cnvtopo_usegtopo30
Definition: mod_cnvtopo.F90:36
module profiler
Definition: scale_prof.F90:11
real(rp), public const_eps
small number
Definition: scale_const.F90:33
module Atmosphere GRID CartesC Real(real space)
module PRECISION
subroutine, public file_tiledata_get_info(TILE_nlim, TILE_DLAT, TILE_DLON, DOMAIN_LATS, DOMAIN_LATE, DOMAIN_LONS, DOMAIN_LONE, catalog_fname, GLOBAL_IA, TILE_nmax, TILE_fname, TILE_hit, TILE_JS, TILE_JE, TILE_IS, TILE_IE, nLATH, nLONH, jsh, jeh, ish, ieh, single_fname, LATS, LATE, LONS, LONE)
get tile information
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]
module Statistics
subroutine, public interp_factor2d(npoints, IA_ref, JA_ref, lon_ref, lat_ref, IA, JA, lon, lat, idx_i, idx_j, hfact, search_limit, latlon_structure, weight_order)
module STDIO
Definition: scale_io.F90:10
logical, public cnvtopo_usegmted2010
Definition: mod_cnvtopo.F90:37