SURFEX v8.1
General documentation of Surfex
hor_interpol_latlon.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_latlon(KLUOUT,PFIELDIN,PFIELDOUT)
7 ! #################################################################################
8 !
9 !!**** *HOR_INTERPOL_LATLON* - Interpolation from a lat/lon regular grid
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! C. Lebeaupin Brossier
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! B. Decharme 07/2014 use usual HORIBL_SURF for regular lat/lon grid
29 !! (ADAPT_HORIBL_SURF is not up to date and is wrong
30 !! for interpolation from a coarse grid to a finer)
31 !!
32 !!------------------------------------------------------------------
33 !
34 !
35 !
36 USE modd_surfex_mpi, ONLY : nrank, npio
38  xla, xola, xolo, np, xloph
39 USE modd_prep, ONLY : xlat_out, xlon_out, linterp
42 USE modd_surf_par, ONLY : xundef
43 !
44 USE modi_horibl_surf_gridin
45 USE modi_horibl_surf_value
46 USE modi_horibl_surf_extrap
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 declarations of arguments
54 !
55 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
56 REAL, DIMENSION(:,:), INTENT(IN) :: PFIELDIN ! field to interpolate horizontally
57 REAL, DIMENSION(:,:), INTENT(OUT) :: PFIELDOUT ! interpolated field
58 !
59 !* 0.2 declarations of local variables
60 !
61 REAL, DIMENSION(:,:), POINTER :: ZFIELDIN0
62 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZFIELDIN
63 !
64 INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: ILSMIN
65 INTEGER, DIMENSION(:,:), ALLOCATABLE :: IMASKIN ! input mask
66 INTEGER, DIMENSION(:), ALLOCATABLE :: IMASKOUT ! output mask
67 INTEGER, DIMENSION(:), POINTER :: IMASK=>null()
68 INTEGER, DIMENSION(SIZE(NP,1),SIZE(NP,2)) :: IP
69 INTEGER :: INO, INL ! output number of points
70 INTEGER :: JL, JI ! loop counter
71 !
72 REAL(KIND=JPRB) :: ZHOOK_HANDLE
73 !
74 !-------------------------------------------------------------------------------------
75 !* 1. Allocations
76 !
77 IF (lhook) CALL dr_hook('HOR_INTERPOL_LATLON',0,zhook_handle)
78 !
79 ino = SIZE(xlat_out)
80 inl = SIZE(pfieldout,2)
81 !
82 ALLOCATE(imaskout(ino))
83 imaskout = 1
84 !
85 ALLOCATE(imaskin(nilength,inl))
86 !
87 IF (nrank==npio) THEN
88  imaskin(:,:) = 1.
89  WHERE(pfieldin(:,:)==xundef) imaskin(:,:) = 0.
90 ENDIF
91 !
92 ALLOCATE(zfieldin(ino,inl,12))
93 ALLOCATE(ilsmin(ino,inl,12))
94 !
95 !
96  CALL horibl_surf_gridin(ninlat,ninlon,nilength,pfieldin(:,:),ino, &
97  .false.,kluout,lglobs,lglobn,lgloblon,np, &
98  zfieldin0,zfieldin,ilsmin,imaskin,imaskout,imask)
99 !
100 DO jl=1,SIZE(np,2)
101  DO ji = 1,SIZE(np,1)
102  ip(ji,jl) = imask(np(ji,jl))
103  ENDDO
104 ENDDO
105 !
106 !* 3. Interpolation with horibl
107 !
108 DO jl=1,inl
109 !
110  CALL horibl_surf_value(nilength,ino,pfieldout(:,jl),linterp,zfieldin(:,jl,:),&
111  ilsmin(:,jl,:),xolo,xola,xla,xloph,imaskin(:,jl),imaskout)
112 !
113 ENDDO
114 !
116  pfieldin,ino,ip,xlon_out,xlat_out,&
117  pfieldout,kluout,linterp,xilatarray)
118 !
119 !* 6. Deallocations
120 !
121 imask => null()
122 DEALLOCATE(imaskin )
123 DEALLOCATE(imaskout)
124 DEALLOCATE(zfieldin)
125 DEALLOCATE(zfieldin0)
126 DEALLOCATE(ilsmin)
127 !
128 IF (lhook) CALL dr_hook('HOR_INTERPOL_LATLON',1,zhook_handle)
129 !-------------------------------------------------------------------------------
130 END SUBROUTINE hor_interpol_latlon
integer, dimension(:), allocatable ninloh
Definition: modd_horibl.F90:39
real, dimension(:), allocatable xilatarray
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
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
subroutine hor_interpol_latlon(KLUOUT, PFIELDIN, PFIELDOUT)
logical lhook
Definition: yomhook.F90:15
integer, dimension(:), allocatable ninlon
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)