SCALE-RM
Data Types | Functions/Subroutines | Variables
scale_interpolation_nest Module Reference

module INTERPOLATION (nesting system) More...

Functions/Subroutines

subroutine, public intrpnest_setup (interp_search_divnum, NEST_INTERP_LEVEL, NEST_INTERP_WEIGHT_ORDER, OFFLINE)
 Setup. More...
 
subroutine, public intrpnest_interp_fact_latlon (hfact, igrd, jgrd, mylat, mylon, myIA, myJA, inlat, inlon, inIA, inJA)
 
subroutine, public intrpnest_interp_fact_llz (hfact, vfact, kgrd, igrd, jgrd, ncopy, myhgt, mylat, mylon, myKS, myKE, myIA, myJA, inhgt, inlat, inlon, inKA, inIA, inJA, landgrid)
 
subroutine, public intrpnest_domain_compatibility (lon_org, lat_org, lev_org, lon_loc, lat_loc, lev_loc, skip_x, skip_y, skip_z)
 

Variables

procedure(intrpnest_intfc_interp_2d), pointer, public intrpnest_interp_2d => NULL()
 
procedure(intrpnest_intfc_interp_3d), pointer, public intrpnest_interp_3d => NULL()
 

Detailed Description

module INTERPOLATION (nesting system)

Description
INTERPOLATION module for nesting system
Author
Team SCALE
History
  • 2015-02-10 (R.Yoshida) [new] rearranged sub-routines

Function/Subroutine Documentation

◆ intrpnest_setup()

subroutine, public scale_interpolation_nest::intrpnest_setup ( integer, intent(in)  interp_search_divnum,
integer, intent(in)  NEST_INTERP_LEVEL,
integer, intent(in)  NEST_INTERP_WEIGHT_ORDER,
logical, intent(in)  OFFLINE 
)

Setup.

Definition at line 233 of file scale_interpolation_nest.F90.

References intrpnest_interp_2d, intrpnest_interp_3d, scale_stdio::io_fid_log, scale_stdio::io_l, and scale_process::prc_mpistop().

Referenced by scale_grid_nest::nest_setup().

233  use scale_process, only: &
235  implicit none
236 
237  integer, intent(in) :: interp_search_divnum
238  integer, intent(in) :: NEST_INTERP_LEVEL
239  integer, intent(in) :: NEST_INTERP_WEIGHT_ORDER
240  logical, intent(in) :: OFFLINE
241 
242  character(len=7) :: select_type
243  !---------------------------------------------------------------------------
244 
245  if( io_l ) write(io_fid_log,*)
246  if( io_l ) write(io_fid_log,*) '++++++ Module[INTERP NEST] / Categ[ATMOS-RM GRID] / Origin[SCALElib]'
247 
248  divnum = interp_search_divnum
249  weight_order = nest_interp_weight_order
250 
251  select case( nest_interp_level )
252  case( 1 )
253  intrpnest_search_horiz => intrpnest_search_horiz_1points
254  intrpnest_interp_2d => intrpnest_interp_2d_1points
255  intrpnest_interp_3d => intrpnest_interp_3d_1points
256  itp_nh = 1
257 
258  case( 3 )
259  intrpnest_search_horiz => intrpnest_search_horiz_3points
260  intrpnest_interp_2d => intrpnest_interp_2d_3points
261  intrpnest_interp_3d => intrpnest_interp_3d_3points
262  itp_nh = 3
263 
264  case( 4 )
265  intrpnest_search_horiz => intrpnest_search_horiz_4points
266  intrpnest_interp_2d => intrpnest_interp_2d_4points
267  intrpnest_interp_3d => intrpnest_interp_3d_4points
268  itp_nh = 4
269 
270  case( 5 )
271  intrpnest_search_horiz => intrpnest_search_horiz_5points
272  intrpnest_interp_2d => intrpnest_interp_2d_5points
273  intrpnest_interp_3d => intrpnest_interp_3d_5points
274  itp_nh = 5
275 
276  case( 8 )
277  intrpnest_search_horiz => intrpnest_search_horiz_8points
278  intrpnest_interp_2d => intrpnest_interp_2d_8points
279  intrpnest_interp_3d => intrpnest_interp_3d_8points
280  itp_nh = 8
281 
282  case( 12 )
283  intrpnest_search_horiz => intrpnest_search_horiz_12points
284  intrpnest_interp_2d => intrpnest_interp_2d_12points
285  intrpnest_interp_3d => intrpnest_interp_3d_12points
286  itp_nh = 12
287 
288  case default
289  write(*,*) 'xxx invarid NEST_INTERP_LEVEL (', nest_interp_level, &
290  ') [setup: nest/interp]'
291  call prc_mpistop
292  end select
293 
294  if ( offline ) then
295  select_type = "offline"
296  intrpnest_search_vert => intrpnest_search_vert_offline
297  else
298  select_type = "online"
299  intrpnest_search_vert => intrpnest_search_vert_online
300  endif
301 
302  if( io_l ) write(io_fid_log,*)
303  if( io_l ) write(io_fid_log,*) '*** Horizontal interpolation with ', nest_interp_level, " points."
304  if( io_l ) write(io_fid_log,*) '*** Vertical interpolation : ', trim(select_type)
305 
306  return
subroutine, public prc_mpistop
Abort MPI.
module PROCESS
procedure(intrpnest_intfc_interp_3d), pointer, public intrpnest_interp_3d
Here is the call graph for this function:
Here is the caller graph for this function:

◆ intrpnest_interp_fact_latlon()

subroutine, public scale_interpolation_nest::intrpnest_interp_fact_latlon ( real(rp), dimension(:,:,:), intent(out)  hfact,
integer, dimension (:,:,:), intent(out)  igrd,
integer, dimension (:,:,:), intent(out)  jgrd,
real(rp), dimension(:,:), intent(in)  mylat,
real(rp), dimension(:,:), intent(in)  mylon,
integer, intent(in)  myIA,
integer, intent(in)  myJA,
real(rp), dimension(:,:), intent(in)  inlat,
real(rp), dimension(:,:), intent(in)  inlon,
integer, intent(in)  inIA,
integer, intent(in)  inJA 
)

Definition at line 324 of file scale_interpolation_nest.F90.

References scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, and scale_process::prc_mpistop().

Referenced by mod_copytopo::copytopo(), mod_realinput::land_interporation(), and mod_realinput::parentatomsetup().

324  use scale_process, only: &
326  implicit none
327 
328  real(RP), intent(out) :: hfact(:,:,:) ! horizontal interp factor
329  integer, intent(out) :: igrd (:,:,:) ! grid points of interp target
330  integer, intent(out) :: jgrd (:,:,:) ! grid points of interp target
331 
332  real(RP), intent(in) :: mylat(:,:) ! latitude data of mine
333  real(RP), intent(in) :: mylon(:,:) ! longitude data of mine
334  integer, intent(in) :: myIA ! grid number of mine
335  integer, intent(in) :: myJA ! grid number of mine
336 
337  real(RP), intent(in) :: inlat(:,:) ! latitude data of you (input)
338  real(RP), intent(in) :: inlon(:,:) ! longitude data of you (input)
339  integer, intent(in) :: inIA ! grid number of you (input)
340  integer, intent(in) :: inJA ! grid number of you (input)
341 
342  integer :: i, j
343  integer :: is, ie
344  integer :: js, je
345  !---------------------------------------------------------------------------
346 
347  hfact(:,:,:) = 0.0_rp
348 
349  do j = 1, myja
350  do i = 1, myia
351  ! nearest block search
352  call intrpnest_search_nearest_block( is, ie, js, je, &
353  mylat(i,j), mylon(i,j), &
354  inlat(:,:), inlon(:,:), &
355  inia, inja )
356 
357  ! main search
358  call intrpnest_search_horiz( hfact(i,j,:), &
359  igrd(i,j,:), &
360  jgrd(i,j,:), &
361  mylat(i,j), &
362  mylon(i,j), &
363  inlat, &
364  inlon, &
365  is, ie, &
366  js, je )
367  enddo
368  enddo
369 
370  return
subroutine, public prc_mpistop
Abort MPI.
module PROCESS
Here is the call graph for this function:
Here is the caller graph for this function:

◆ intrpnest_interp_fact_llz()

subroutine, public scale_interpolation_nest::intrpnest_interp_fact_llz ( real(rp), dimension(:,:,:), intent(out)  hfact,
real(rp), dimension(:,:,:,:,:), intent(out)  vfact,
integer, dimension (:,:,:,:,:), intent(out)  kgrd,
integer, dimension (:,:,:), intent(out)  igrd,
integer, dimension (:,:,:), intent(out)  jgrd,
integer, dimension(:,:,:), intent(out)  ncopy,
real(rp), dimension(:,:,:), intent(in)  myhgt,
real(rp), dimension(:,:), intent(in)  mylat,
real(rp), dimension(:,:), intent(in)  mylon,
integer, intent(in)  myKS,
integer, intent(in)  myKE,
integer, intent(in)  myIA,
integer, intent(in)  myJA,
real(rp), dimension(:,:,:), intent(in)  inhgt,
real(rp), dimension(:,:), intent(in)  inlat,
real(rp), dimension(:,:), intent(in)  inlon,
integer, intent(in)  inKA,
integer, intent(in)  inIA,
integer, intent(in)  inJA,
logical, intent(in), optional  landgrid 
)

Definition at line 397 of file scale_interpolation_nest.F90.

References scale_const::const_eps, scale_grid_index::ia, scale_grid_index::ie, scale_grid_index::is, scale_grid_index::ja, scale_grid_index::je, scale_grid_index::js, scale_grid_index::ke, scale_grid_index::khalo, scale_grid_index::ks, scale_land_grid_index::lkmax, and scale_process::prc_mpistop().

Referenced by mod_realinput::land_interporation(), scale_grid_nest::nest_setup(), mod_realinput_scale::parentatominputscale(), and mod_realinput::parentatomsetup().

397  use scale_process, only: &
399  implicit none
400 
401  real(RP), intent(out) :: hfact(:,:,:) ! horizontal interp factor
402  real(RP), intent(out) :: vfact(:,:,:,:,:) ! vertical interp factor
403  integer, intent(out) :: kgrd (:,:,:,:,:) ! grid points of interp target
404  integer, intent(out) :: igrd (:,:,:) ! grid points of interp target
405  integer, intent(out) :: jgrd (:,:,:) ! grid points of interp target
406  integer, intent(out) :: ncopy(:,:,:) ! number of daughter's layers below parent lowest layer
407 
408  real(RP), intent(in) :: myhgt(:,:,:) ! height data of mine
409  real(RP), intent(in) :: mylat(:,:) ! latitude data of mine
410  real(RP), intent(in) :: mylon(:,:) ! longitude data of mine
411  integer, intent(in) :: myKS ! start grid number of mine
412  integer, intent(in) :: myKE ! end grid number of mine
413  integer, intent(in) :: myIA ! grid number of mine
414  integer, intent(in) :: myJA ! grid number of mine
415 
416  real(RP), intent(in) :: inhgt(:,:,:) ! height data of you (input)
417  real(RP), intent(in) :: inlat(:,:) ! latitude data of you (input)
418  real(RP), intent(in) :: inlon(:,:) ! longitude data of you (input)
419  integer, intent(in) :: inKA ! grid number of you (input)
420  integer, intent(in) :: inIA ! grid number of you (input)
421  integer, intent(in) :: inJA ! grid number of you (input)
422 
423  logical, intent(in), optional :: landgrid
424 
425  integer :: i, j
426  integer :: is, ie
427  integer :: js, je
428  logical :: lndgrd
429  !---------------------------------------------------------------------------
430 
431  lndgrd = .false.
432  if ( present(landgrid) ) then
433  if ( landgrid ) then
434  lndgrd = .true.
435  endif
436  endif
437 
438  hfact(:,:,:) = 0.0_rp
439  vfact(:,:,:,:,:) = 0.0_rp
440  ncopy(:,:,:) = 0
441 
442  do j = 1, myja
443  do i = 1, myia
444 
445  ! nearest block search
446  call intrpnest_search_nearest_block( is, ie, js, je, &
447  mylat(i,j), mylon(i,j), &
448  inlat(:,:), inlon(:,:), &
449  inia, inja )
450 
451  ! main search
452  call intrpnest_search_horiz( hfact(i,j,:), &
453  igrd(i,j,:), &
454  jgrd(i,j,:), &
455  mylat(i,j), &
456  mylon(i,j), &
457  inlat, &
458  inlon, &
459  is, ie, &
460  js, je )
461 
462 
463  call intrpnest_search_vert( vfact, &
464  kgrd, &
465  ncopy(i,j,:), &
466  igrd(i,j,:), &
467  jgrd(i,j,:), &
468  myhgt(:,i,j), &
469  inhgt, &
470  i, j, &
471  myks, myke, &
472  inka, &
473  lndgrd )
474 
475  enddo
476  enddo
477 
478  return
subroutine, public prc_mpistop
Abort MPI.
module PROCESS
Here is the call graph for this function:
Here is the caller graph for this function:

◆ intrpnest_domain_compatibility()

subroutine, public scale_interpolation_nest::intrpnest_domain_compatibility ( real(rp), dimension(:,:), intent(in)  lon_org,
real(rp), dimension(:,:), intent(in)  lat_org,
real(rp), dimension(:,:,:), intent(in)  lev_org,
real(rp), dimension(:,:), intent(in)  lon_loc,
real(rp), dimension(:,:), intent(in)  lat_loc,
real(rp), dimension(:,:,:), intent(in)  lev_loc,
logical, intent(in), optional  skip_x,
logical, intent(in), optional  skip_y,
logical, intent(in), optional  skip_z 
)

Definition at line 2168 of file scale_interpolation_nest.F90.

References scale_const::const_d2r, and scale_process::prc_mpistop().

Referenced by mod_copytopo::copytopo(), and mod_realinput::parentatomsetup().

2168  use scale_process, only: &
2169  prc_mpistop
2170  use scale_const, only: &
2171  d2r => const_d2r
2172  implicit none
2173  real(RP), intent(in) :: lon_org(:,:)
2174  real(RP), intent(in) :: lat_org(:,:)
2175  real(RP), intent(in) :: lev_org(:,:,:)
2176  real(RP), intent(in) :: lon_loc(:,:)
2177  real(RP), intent(in) :: lat_loc(:,:)
2178  real(RP), intent(in) :: lev_loc(:,:,:)
2179  logical, intent(in), optional :: skip_x
2180  logical, intent(in), optional :: skip_y
2181  logical, intent(in), optional :: skip_z
2182 
2183  real(RP) :: max_ref, min_ref
2184  real(RP) :: max_loc, min_loc
2185 
2186  logical :: do_xdirec
2187  logical :: do_ydirec
2188  logical :: do_zdirec
2189 
2190  intrinsic size
2191  !---------------------------------------------------------------------------
2192 
2193  do_xdirec = .true.
2194  if ( present(skip_x) ) then
2195  if ( skip_x ) then
2196  do_xdirec = .false.
2197  endif
2198  endif
2199 
2200  do_ydirec = .true.
2201  if ( present(skip_y) ) then
2202  if ( skip_y ) then
2203  do_ydirec = .false.
2204  endif
2205  endif
2206 
2207  do_zdirec = .true.
2208  if ( present(skip_z) ) then
2209  if ( skip_z ) then
2210  do_zdirec = .false.
2211  endif
2212  endif
2213 
2214  if ( do_xdirec ) then
2215  max_ref = maxval( lon_org(:,:) / d2r )
2216  min_ref = minval( lon_org(:,:) / d2r )
2217  max_loc = maxval( lon_loc(:,:) / d2r )
2218  min_loc = minval( lon_loc(:,:) / d2r )
2219 
2220  if ( (min_ref+360.0_rp-max_ref) < 360.0_rp / size(lon_org,1) * 2.0_rp) then
2221  ! cyclic OK
2222  else if ( max_ref < max_loc .OR. min_ref > min_loc ) then
2223  write(*,*) 'xxx ERROR: REQUESTED DOMAIN IS TOO MUCH BROAD'
2224  write(*,*) 'xxx -- LONGITUDINAL direction over the limit'
2225  write(*,*) 'xxx -- reference max: ', max_ref
2226  write(*,*) 'xxx -- reference min: ', min_ref
2227  write(*,*) 'xxx -- local max: ', max_loc
2228  write(*,*) 'xxx -- local min: ', min_loc
2229  call prc_mpistop
2230  endif
2231  endif
2232 
2233  if ( do_ydirec ) then
2234  max_ref = maxval( lat_org(:,:) / d2r )
2235  min_ref = minval( lat_org(:,:) / d2r )
2236  max_loc = maxval( lat_loc(:,:) / d2r )
2237  min_loc = minval( lat_loc(:,:) / d2r )
2238 
2239  if ( max_ref < max_loc .OR. min_ref > min_loc ) then
2240  write(*,*) 'xxx ERROR: REQUESTED DOMAIN IS TOO MUCH BROAD'
2241  write(*,*) 'xxx -- LATITUDINAL direction over the limit'
2242  write(*,*) 'xxx -- reference max: ', max_ref
2243  write(*,*) 'xxx -- reference min: ', min_ref
2244  write(*,*) 'xxx -- local max: ', max_loc
2245  write(*,*) 'xxx -- local min: ', min_loc
2246  call prc_mpistop
2247  endif
2248  endif
2249 
2250  if ( do_zdirec ) then
2251  max_ref = maxval( lev_org(:,:,:) )
2252  !max_loc = maxval( lev_loc(KS-1:KE+1,:,:) ) ! HALO + 1
2253  max_loc = maxval( lev_loc(:,:,:) ) ! HALO + 1
2254  !min_ref = minval( lev_org(:,:,:) )
2255  !min_loc = minval( lev_loc(3:KA,:,:) ) ! HALO + 1
2256 
2257  if ( max_ref < max_loc ) then
2258  !if ( max_ref < max_loc .OR. min_ref > min_loc ) then
2259  write(*,*) 'xxx ERROR: REQUESTED DOMAIN IS TOO MUCH BROAD'
2260  write(*,*) 'xxx -- VERTICAL direction over the limit'
2261  write(*,*) 'xxx -- reference max: ', max_ref
2262  !write(*,*) 'xxx -- reference min: ', min_ref
2263  write(*,*) 'xxx -- local max: ', max_loc
2264  !write(*,*) 'xxx -- local min: ', min_loc
2265  call prc_mpistop
2266  endif
2267  endif
2268 
2269  return
subroutine, public prc_mpistop
Abort MPI.
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ intrpnest_interp_2d

procedure(intrpnest_intfc_interp_2d), pointer, public scale_interpolation_nest::intrpnest_interp_2d => NULL()

Definition at line 164 of file scale_interpolation_nest.F90.

Referenced by mod_copytopo::copytopo(), intrpnest_setup(), mod_realinput::land_interporation(), mod_realinput_scale::parentatominputscale(), and mod_realinput::parentatomsetup().

164  procedure(INTRPNEST_intfc_interp_2d), pointer :: INTRPNEST_interp_2d => null()

◆ intrpnest_interp_3d

procedure(intrpnest_intfc_interp_3d), pointer, public scale_interpolation_nest::intrpnest_interp_3d => NULL()

Definition at line 199 of file scale_interpolation_nest.F90.

Referenced by intrpnest_setup(), mod_realinput::land_interporation(), scale_grid_nest::nest_comm_intercomm_nestdown_3d(), mod_realinput_scale::parentatominputscale(), and mod_realinput::parentatomsetup().

199  procedure(INTRPNEST_intfc_interp_3d), pointer :: INTRPNEST_interp_3d => null()