SURFEX v8.1
General documentation of Surfex
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_surfex_mpi, ONLY : nrank, npio
34  xla, xola, xolo, np, xloph
35 USE modd_prep, ONLY : xlat_out, xlon_out,linterp
36 USE modd_grid_arome, ONLY : xx, xy, nx, ny, xlat0, xlon0, xlator, xlonor, xrpk, xbeta, &
37  xzx, xzy, nix
38 USE modd_grid_grib, ONLY : nni
39 USE modd_surf_par, ONLY : xundef
40 !
41 USE modi_horibl_surf_gridin
42 USE modi_horibl_surf_value
43 USE modi_horibl_surf_extrap
44 !
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 declarations of arguments
52 !
53 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
54 REAL, DIMENSION(:,:), INTENT(IN) :: PFIELDIN ! field to interpolate horizontally
55 REAL, DIMENSION(:,:), INTENT(OUT) :: PFIELDOUT ! interpolated field
56 !
57 !* 0.2 declarations of local variables
58 !
59 REAL, DIMENSION(:,:), POINTER :: ZFIELDIN0
60 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZFIELDIN
61 !
62 INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: ILSMIN
63 INTEGER, DIMENSION(:,:), ALLOCATABLE :: IMASKIN ! input mask
64 INTEGER, DIMENSION(:), ALLOCATABLE :: IMASKOUT ! output mask
65 INTEGER, DIMENSION(:), POINTER :: IMASK=>null()
66 INTEGER, DIMENSION(SIZE(NP,1),SIZE(NP,2)) :: IP
67 INTEGER :: INO, INL ! output number of points
68 INTEGER :: JL, JI ! loop counter
69 REAL(KIND=JPRB) :: ZHOOK_HANDLE
70 !
71 !-------------------------------------------------------------------------------------
72 !
73 !* 1. Allocations
74 !
75 IF (lhook) CALL dr_hook('HOR_INTERPOL_AROME',0,zhook_handle)
76 ino = SIZE(xlat_out)
77 inl = SIZE(pfieldout,2)
78 !
79 ALLOCATE(imaskout(ino))
80 imaskout = 1
81 !
82 ALLOCATE(imaskin(nni,inl))
83 !
84 IF (nrank==npio) THEN
85  imaskin(:,:) = 1.
86  WHERE(pfieldin(:,:)==xundef) imaskin(:,:) = 0.
87 ENDIF
88 !
89 ALLOCATE(zfieldin(ino,inl,12))
90 ALLOCATE(ilsmin(ino,inl,12))
91 !
92  CALL horibl_surf_gridin(ny,nix,nni,pfieldin(:,:),ino, &
93  .false.,kluout,lglobs,lglobn,lgloblon,np, &
94  zfieldin0,zfieldin,ilsmin,imaskin,imaskout,imask)
95 !
96 DO jl=1,SIZE(np,2)
97  DO ji = 1,SIZE(np,1)
98  ip(ji,jl) = imask(np(ji,jl))
99  ENDDO
100 ENDDO
101 !
102 !* 3. Input mask
103 !
104 DO jl=1,inl
105 !
106  CALL horibl_surf_value(nni,ino,pfieldout(:,jl),linterp,zfieldin(:,jl,:),ilsmin(:,jl,:),&
107  xolo,xola,xla,xloph,imaskin(:,jl),imaskout)
108 !
109 ENDDO
110 !
111  CALL horibl_surf_extrap(0.,xilo1h,xy,xilo2h,ny,nix,nni,pfieldin,&
112  ino,ip,xzx,xzy,pfieldout,kluout,linterp)
113 !
114 !* 5. Deallocations
115 !
116 imask => null()
117 DEALLOCATE(imaskin )
118 DEALLOCATE(imaskout)
119 DEALLOCATE(zfieldin0)
120 DEALLOCATE(zfieldin)
121 DEALLOCATE(ilsmin)
122 !
123 IF (lhook) CALL dr_hook('HOR_INTERPOL_AROME',1,zhook_handle)
124 !
125 !-------------------------------------------------------------------------------------
126 END SUBROUTINE hor_interpol_arome
integer, dimension(:), allocatable ninloh
Definition: modd_horibl.F90:39
real, dimension(:), allocatable xzy
real, dimension(:), allocatable xola
Definition: modd_horibl.F90:41
integer, dimension(:,:), allocatable np
Definition: modd_horibl.F90:42
real, dimension(:), allocatable xlon_out
Definition: modd_prep.F90:48
logical lgloblon
Definition: modd_horibl.F90:35
real, parameter xundef
logical, dimension(:), allocatable linterp
Definition: modd_prep.F90:43
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:), allocatable xzx
subroutine horibl_surf_gridin(KINLA, KINLO, KILEN, PARIN, KOLEN, ODVECT, KLUOUT, OGLOBS, OGLOBN, OGLOBLON, KP, PARIN0_OUT, PARIN_OUT, KLSMIN_OUT, KLSMIN, KLSMOUT, KMASK)
real, dimension(:), allocatable xlat_out
Definition: modd_prep.F90:47
integer, dimension(:), allocatable nix
logical lglobs
Definition: modd_horibl.F90:35
real, dimension(:), allocatable xolo
Definition: modd_horibl.F90:41
subroutine hor_interpol_arome(KLUOUT, PFIELDIN, PFIELDOUT)
logical lhook
Definition: yomhook.F90:15
logical lglobn
Definition: modd_horibl.F90:35
real, dimension(:,:), allocatable xla
Definition: modd_horibl.F90:40
subroutine horibl_surf_extrap(PILA1, PILO1, PILA2, PILO2, KINLA, KINLO, KILEN, PARIN, KOLEN, KP, PXOUT, PYOUT, PAROUT, KLUOUT, OINTERP, PILATARRAY)
real, dimension(:,:), allocatable xloph
Definition: modd_horibl.F90:43
subroutine horibl_surf_value(KILEN, KOLEN, PAROUT, OINTERP, PARIN, KLSMIN, POLO, POLA, PLA, PLOP, KMASKIN, KLSMOUT)