SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
hor_interpol_arome.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6 SUBROUTINE hor_interpol_arome(KLUOUT,PFIELDIN,PFIELDOUT)
7 ! #################################################################################
8 !
9 !!**** *HOR_INTERPOL_AROME * - Interpolation from an AROME grid
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !!------------------------------------------------------------------
29 !
30 !
31 !
32 USE modd_prep, ONLY : xlat_out, xlon_out,linterp
33 USE modd_grid_arome, ONLY : xx, xy, nx, ny, xlat0, xlon0, xlator, xlonor, xrpk, xbeta
34 USE modd_grid_grib, ONLY : nni
35 USE modd_surf_par, ONLY : xundef
36 !
38 USE modi_horibl_surf
39 !
40 !
41 USE yomhook ,ONLY : lhook, dr_hook
42 USE parkind1 ,ONLY : jprb
43 !
44 IMPLICIT NONE
45 !
46 !* 0.1 declarations of arguments
47 !
48 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
49 REAL, DIMENSION(:,:), INTENT(IN) :: pfieldin ! field to interpolate horizontally
50 REAL, DIMENSION(:,:), INTENT(OUT) :: pfieldout ! interpolated field
51 !
52 !* 0.2 declarations of local variables
53 !
54 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X coordinate
55 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y coordinate
56 INTEGER, DIMENSION(:), ALLOCATABLE :: imaskin ! input mask
57 INTEGER, DIMENSION(:), ALLOCATABLE :: imaskout ! output mask
58 INTEGER :: ino ! output number of points
59 INTEGER :: jl ! loop counter
60 INTEGER, DIMENSION(:), ALLOCATABLE :: ix ! number of points on each line
61 REAL(KIND=JPRB) :: zhook_handle
62 !
63 !-------------------------------------------------------------------------------------
64 !
65 !* 1. Allocations
66 !
67 IF (lhook) CALL dr_hook('HOR_INTERPOL_AROME',0,zhook_handle)
68 ino = SIZE(xlat_out)
69 !
70 ALLOCATE(imaskin(nni))
71 !
72 ALLOCATE(zx(ino))
73 ALLOCATE(zy(ino))
74 ALLOCATE(imaskout(ino))
75 imaskout = 1
76 ALLOCATE(ix(ny))
77 ix=nx
78 !
79 !* 2. Transformation of latitudes/longitudes into metric coordinates of input grid
80 !
81  CALL xy_conf_proj(xlat0,xlon0,xrpk,xbeta,xlator,xlonor,zx,zy,xlat_out,xlon_out)
82 !
83 !
84 !* 3. Input mask
85 !
86 DO jl=1,SIZE(pfieldin,2)
87  imaskin(:) = 1
88  WHERE(pfieldin(:,jl)==xundef) imaskin = 0
89 !
90 !
91 !* 4. Interpolation with horibl
92 !
93  CALL horibl_surf(0.,0.,xy,xx,ny,ix,nni,pfieldin(:,jl),ino,zx,zy,pfieldout(:,jl), &
94  .false.,kluout,linterp,imaskin,imaskout)
95 END DO
96 !
97 !* 5. Deallocations
98 !
99 DEALLOCATE(zx)
100 DEALLOCATE(ix)
101 DEALLOCATE(zy)
102 DEALLOCATE(imaskin )
103 DEALLOCATE(imaskout)
104 IF (lhook) CALL dr_hook('HOR_INTERPOL_AROME',1,zhook_handle)
105 
106 !-------------------------------------------------------------------------------------
107 END SUBROUTINE hor_interpol_arome
subroutine horibl_surf(PILA1, PILO1, PILA2, PILO2, KINLA, KINLO, KILEN, PARIN, KOLEN, PXOUT, PYOUT, PAROUT, ODVECT, KLUOUT, OINTERP, KLSMIN, KLSMOUT)
Definition: horibl_surf.F90:6
subroutine hor_interpol_arome(KLUOUT, PFIELDIN, PFIELDOUT)
subroutine xy_conf_proj(PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, PX, PY, PLAT, PLON)