SURFEX v8.1
General documentation of Surfex
hor_interpol_gauss.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_gauss(KLUOUT,PFIELDIN,PFIELDOUT)
7 ! #################################################################################
8 !
9 !!**** *HOR_INTERPOL_GAUSS* - Interpolation from a gaussian grid
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !! AUTHOR
21 !! ------
22 !! V. Masson
23 !!
24 !! MODIFICATIONS
25 !! -------------
26 !! Original 01/2004
27 !! M. Jidane Dec 2013 : initialize NNI if not already done
28 !!------------------------------------------------------------------
29 !
30 USE modd_surfex_mpi, ONLY : nrank, npio
32  xla, xola, xolo, np, xloph
33 USE modd_prep, ONLY : xlat_out, xlon_out, linterp
35  xlap, xlop, xcoef, xlat, xlon
36 USE modd_grid_grib, ONLY : nni
37 USE modd_surf_par, ONLY : xundef
38 !
39 USE modi_horibl_surf_gridin
40 USE modi_horibl_surf_value
41 USE modi_horibl_surf_extrap
42 !
43 USE yomhook ,ONLY : lhook, dr_hook
44 USE parkind1 ,ONLY : jprb
45 !
46 IMPLICIT NONE
47 !
48 !* 0.1 declarations of arguments
49 !
50 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
51 REAL, DIMENSION(:,:), INTENT(IN) :: PFIELDIN ! field to interpolate horizontally
52 REAL, DIMENSION(:,:), INTENT(OUT) :: PFIELDOUT ! interpolated field
53 !
54 !* 0.2 declarations of local variables
55 !
56 REAL, DIMENSION(:,:), POINTER :: ZFIELDIN0=>null()
57 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZFIELDIN
58 !
59 INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: ILSMIN
60 INTEGER, DIMENSION(:,:), ALLOCATABLE :: IMASKIN ! input mask
61 INTEGER, DIMENSION(:), ALLOCATABLE :: IMASKOUT ! output mask
62 INTEGER, DIMENSION(:), POINTER :: IMASK=>null()
63 INTEGER, DIMENSION(SIZE(NP,1),SIZE(NP,2)) :: IP
64 INTEGER :: INO, INL ! output number of points
65 INTEGER :: JL, JI ! loop counter
66 REAL(KIND=JPRB) :: ZHOOK_HANDLE
67 !
68 !-------------------------------------------------------------------------------------
69 !
70 !* 1. Allocations
71 !
72 IF (lhook) CALL dr_hook('HOR_INTERPOL_GAUSS',0,zhook_handle)
73 ino = SIZE(xlat_out)
74 inl = SIZE(pfieldout,2)
75 !
76 ALLOCATE(imaskout(ino))
77 imaskout = 1
78 !
79 IF (nni==0) nni=nilen
80 ALLOCATE(imaskin(nni,inl))
81 !
82 IF (nrank==npio) THEN
83  imaskin(:,:) = 1.
84  WHERE(pfieldin(:,:)==xundef) imaskin(:,:) = 0.
85 ENDIF
86 
87 ALLOCATE(zfieldin(ino,inl,12))
88 ALLOCATE(ilsmin(ino,inl,12))
89 !
90  CALL horibl_surf_gridin(ninla,ninlo,nni,pfieldin(:,:),ino, &
91  .false.,kluout,lglobs,lglobn,lgloblon,np, &
92  zfieldin0,zfieldin,ilsmin,imaskin,imaskout,imask)
93 !
94 DO jl=1,SIZE(np,2)
95  DO ji = 1,SIZE(np,1)
96  ip(ji,jl) = imask(np(ji,jl))
97  ENDDO
98 ENDDO
99 !
100 DO jl=1,SIZE(pfieldout,2)
101  !
102  CALL horibl_surf_value(nni,ino,pfieldout(:,jl),linterp,zfieldin(:,jl,:),ilsmin(:,jl,:),&
103  xolo,xola,xla,xloph,imaskin(:,jl),imaskout)
104  !
105 ENDDO
106 !
108  ino,ip,xlon,xlat,pfieldout,kluout,linterp)
109 !
110 !* 5. Deallocations
111 !
112 imask => null()
113 DEALLOCATE(imaskin )
114 DEALLOCATE(imaskout)
115 DEALLOCATE(zfieldin0)
116 DEALLOCATE(zfieldin)
117 DEALLOCATE(ilsmin)
118 !
119 !-------------------------------------------------------------------------------
120 IF (lhook) CALL dr_hook('HOR_INTERPOL_GAUSS',1,zhook_handle)
121 !
122 END SUBROUTINE hor_interpol_gauss
integer, dimension(:), allocatable ninloh
Definition: modd_horibl.F90:39
real, dimension(:), allocatable xlat
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
subroutine hor_interpol_gauss(KLUOUT, PFIELDIN, PFIELDOUT)
real, parameter xundef
logical, dimension(:), allocatable linterp
Definition: modd_prep.F90:43
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:), allocatable xlon
integer, dimension(:), allocatable ninlo
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
logical lglobs
Definition: modd_horibl.F90:35
real, dimension(:), allocatable xolo
Definition: modd_horibl.F90:41
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)