SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
coef_ver_interp_lin_surf.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 coef_ver_interp_lin_surf(PZ1,PZ2,KKLIN,PCOEFLIN)
7 ! ###############################################################
8 !
9 !!**** *VER_INTERP_LIN* - vertical linear interpolation
10 !!
11 !! PURPOSE
12 !! -------
13 ! This function computes the interpolation coefficient XCOEFLIN
14 ! of the level XKLIN of grid PZ1 which is just under the points of
15 ! grid PZ2 (respectively called hereafter 'initial' and 'target'),
16 ! in order to perform linear interpolations between these 2 grids.
17 !
18 ! CAUTION:
19 ! * The interpolation occurs on the WHOLE grid. Therefore, one must
20 ! only give as argument to this function the inner points of the domain,
21 ! particularly for the vertical grid, where there is no physical information
22 ! under the ground or at and over H.
23 ! * The level numbers must increase from bottom to top.
24 !!
25 !!** METHOD
26 !! ------
27 !! two extrapolations are possible: with the two or four nearest points.
28 !!
29 !! Interpolation with 2 points:
30 !!
31 !! If there is less than two points on one side, the interpolation is linear.
32 !!
33 !! EXTERNAL
34 !! --------
35 !!
36 !! IMPLICIT ARGUMENTS
37 !! ------------------
38 !!
39 !! REFERENCE
40 !! ---------
41 !!
42 !!
43 !! AUTHOR
44 !! ------
45 !!
46 ! V.Masson Meteo-France
47 !!
48 !! MODIFICATIONS
49 !! -------------
50 !! Original 18/07/97
51 !! 20/01/98 use explicit arguments
52 !! P Jabouille 20/12/02 no extrapolation under the ground
53 !! S. Malardel 11/2003 bug of no extrapolation under the ground
54 !! V. Masson 10/2003 no extrapolation above top
55 !-------------------------------------------------------------------------------
56 !
57 !* 0. DECLARATIONS
58 ! ------------
59 !
60 !
61 USE yomhook ,ONLY : lhook, dr_hook
62 USE parkind1 ,ONLY : jprb
63 !
64 IMPLICIT NONE
65 !
66 !* 0.1 Declaration of arguments
67 ! ------------------------
68 REAL, DIMENSION(:,:), INTENT(IN) :: pz1 ! altitudes of the points of the
69 ! ! initial grid
70 REAL, DIMENSION(:,:), INTENT(IN) :: pz2 ! altitudes of the points of the
71 ! ! target grid
72 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kklin ! number of the level
73  ! of the data to be interpolated
74 !
75 REAL, DIMENSION(:,:), INTENT(OUT):: pcoeflin ! interpolation
76  ! coefficient
77 !
78 !
79 !* 0.2 Declaration of local variables
80 ! ------------------------------
81 !
82 LOGICAL,DIMENSION(SIZE(PZ1,1),SIZE(PZ1,2)) :: glevel
83 INTEGER :: jk2,ji
84 INTEGER,DIMENSION(SIZE(PZ1,1)) :: ilevel
85 INTEGER,DIMENSION(SIZE(PZ1,1)) :: iunder
86 REAL :: zeps ! a small number
87 REAL(KIND=JPRB) :: zhook_handle
88 !-------------------------------------------------------------------------------
89 !
90 IF (lhook) CALL dr_hook('COEF_VER_INTERP_LIN_SURF',0,zhook_handle)
91 zeps=1.e-12
92 !
93 !-------------------------------------------------------------------------------
94 !
95 !* 2. LOOP ON THE TARGET VERTICAL GRID
96 ! --------------------------------
97 !
98 DO jk2=1,SIZE(pz2,2)
99 !
100 !-------------------------------------------------------------------------------
101 !
102 !* 3. Determination of the initial level under the target level JK2
103 ! -------------------------------------------------------------
104 !
105  glevel(:,:)=pz1(:,:)<=spread(pz2(:,jk2),2,SIZE(pz1,2)) *(1.-zeps)
106  ilevel(:) =count(glevel(:,:),2)
107 !
108 !* linear extrapolation under the ground
109  iunder=ilevel
110  ilevel(:)=max(ilevel(:),1)
111 !
112 !* linear extrapolation above the uppest level
113  ilevel(:)=min(ilevel(:),SIZE(pz1,2)-1)
114 !
115  kklin(:,jk2)=ilevel(:)
116 
117 !-------------------------------------------------------------------------------
118 !
119 !* 4. Linear interpolation coefficients
120 ! ---------------------------------
121 !
122  DO ji=1,SIZE(pz1,1)
123  IF (pz1(ji,ilevel(ji))==pz1(ji,ilevel(ji)+1)) THEN
124  pcoeflin(ji,jk2)= 0.
125  ELSE
126  pcoeflin(ji,jk2)=(pz2(ji,jk2)-pz1(ji,ilevel(ji)+1)) &
127  /(pz1(ji,ilevel(ji))-pz1(ji,ilevel(ji)+1))
128  END IF
129  IF (iunder(ji) < 1 ) pcoeflin(ji,jk2)=1. ! no extrapolation
130  IF (ilevel(ji)==SIZE(pz1,2)-1) pcoeflin(ji,jk2)=max(pcoeflin(ji,jk2),0.) ! no extrapolation
131  ENDDO
132 !
133 !-------------------------------------------------------------------------------
134 !
135 END DO
136 IF (lhook) CALL dr_hook('COEF_VER_INTERP_LIN_SURF',1,zhook_handle)
137 !
138 !-------------------------------------------------------------------------------
139 !
140 END SUBROUTINE coef_ver_interp_lin_surf
subroutine coef_ver_interp_lin_surf(PZ1, PZ2, KKLIN, PCOEFLIN)