SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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_prep, ONLY : xlat_out, xlon_out, linterp
37 USE modd_grid_latlonregul, ONLY : xilat1, xilon1, xilat2, xilon2, &
38  ninlat, ninlon, nilength,xilatarray
39 USE modd_surf_par, ONLY : xundef
40 !
41 USE modi_horibl_surf
42 USE modi_adapt_horibl_surf
43 !
44 USE yomhook ,ONLY : lhook, dr_hook
45 USE parkind1 ,ONLY : jprb
46 !
47 IMPLICIT NONE
48 !
49 !* 0.1 declarations of arguments
50 !
51 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
52 REAL, DIMENSION(:,:), INTENT(IN) :: pfieldin ! field to interpolate horizontally
53 REAL, DIMENSION(:,:), INTENT(OUT) :: pfieldout ! interpolated field
54 !
55 !* 0.2 declarations of local variables
56 !
57 INTEGER, DIMENSION(:), ALLOCATABLE :: imaskin ! input mask
58 INTEGER, DIMENSION(:), ALLOCATABLE :: imaskout ! output mask
59 INTEGER :: ino ! output number of points
60 INTEGER :: jl ! loop counter
61 LOGICAL :: gregular
62 REAL :: zdlat,zdlat_reg
63 !
64 REAL(KIND=JPRB) :: zhook_handle
65 !
66 !-------------------------------------------------------------------------------------
67 !* 1. Allocations
68 !
69 IF (lhook) CALL dr_hook('HOR_INTERPOL_LATLON',0,zhook_handle)
70 !
71 ino = SIZE(xlat_out)
72 !
73 ALLOCATE(imaskin(nilength))
74 !
75 ALLOCATE(imaskout(ino))
76 !
77 !* 2. Initializations
78 !
79 gregular= .true.
80 !
81 imaskout = 1
82 !
83 zdlat_reg = (xilat2-xilat1)/REAL(ninlat-1)
84 !
85 DO jl=2,ninlat
86  zdlat=xilatarray(jl)-xilatarray(jl-1)
87  IF(zdlat/=zdlat_reg)THEN
88  gregular=.false.
89  ENDIF
90 ENDDO
91 !
92 !
93 !* 3. Interpolation with horibl
94 !
95 IF(gregular)THEN
96  DO jl=1,SIZE(pfieldin,2)
97  imaskin(:) = 1
98  WHERE(pfieldin(:,jl)==xundef) imaskin(:) = 0
99  CALL horibl_surf(xilat1,xilon1,xilat2,xilon2,ninlat,ninlon,nilength, &
100  pfieldin(:,jl),ino,xlon_out,xlat_out,pfieldout(:,jl),.false., &
101  kluout,linterp,imaskin,imaskout)
102  ENDDO
103 ELSE
104  DO jl=1,SIZE(pfieldin,2)
105  imaskin(:) = 1
106  WHERE(pfieldin(:,jl)==xundef) imaskin(:) = 0
107  CALL adapt_horibl_surf(xilatarray,xilat1,xilon1,xilat2,xilon2,ninlat,ninlon,nilength, &
108  pfieldin(:,jl),ino,xlon_out,xlat_out,pfieldout(:,jl),.false., &
109  kluout,linterp,imaskin,imaskout)
110  ENDDO
111 ENDIF
112 !
113 !* 6. Deallocations
114 !
115 IF (ALLOCATED(imaskin )) DEALLOCATE(imaskin )
116 IF (ALLOCATED(imaskout)) DEALLOCATE(imaskout)
117 !
118 IF (lhook) CALL dr_hook('HOR_INTERPOL_LATLON',1,zhook_handle)
119 !-------------------------------------------------------------------------------
120 END SUBROUTINE hor_interpol_latlon
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_latlon(KLUOUT, PFIELDIN, PFIELDOUT)
subroutine adapt_horibl_surf(PILATARRAY, PILA1, PILO1, PILA2, PILO2, KINLA, KINLO, KILEN, PARIN, KOLEN, PXOUT, PYOUT, PAROUT, ODVECT, KLUOUT, OINTERP, KLSMIN, KLSMOUT)