SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
interpol_sbl.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 interpol_sbl( PZ, PIN, PH, POUT)
7 ! #####################################################################
8 !
9 !!
10 !! PURPOSE
11 !! -------
12 ! This routine do interpolation of field from canopy levels to a defined
13 ! height. Interpolation is linear.
14 !
15 !
16 !!** METHOD
17 !! ------
18 ! We search for the levels aroud the specified height of interpolation and
19 ! then perform a linear interpolation. If height of interpolation isn't
20 ! between two canopy levels, we send the value XUNDEF.
21 !
22 !! EXTERNAL
23 !! --------
24 !!
25 !! none
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !!
35 !! AUTHOR
36 !! ------
37 ! Sebastien Riette
38 !!
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !!
43 !! Original 14/01/2010
44 !-------------------------------------------------------------------------------
45 !
46 !* 0. DECLARATIONS
47 ! ------------
48 !
49 USE modd_surf_par, ONLY : xundef
50 !
51 !
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 declarations of arguments
59 !
60 !
61 !
62 REAL, DIMENSION(:,:), INTENT(IN) :: pz ! Height of canopy levels
63 REAL, DIMENSION(:,:), INTENT(IN) :: pin ! Filed values on canopy levels
64 REAL, INTENT(IN) :: ph ! Height of interpolation
65 !
66 REAL, DIMENSION(:) , INTENT(OUT) :: pout ! Interpolated value
67 !
68 !* 0.2 declarations of local variables
69 !
70 INTEGER :: ilevel
71 REAL(KIND=JPRB) :: zhook_handle
72 !
73 !-------------------------------------------------------------------------------
74 !
75 ! Starting from the bottom, we look for the canopy level just below 10m and
76 ! we interpolate linearly the canopy wind field if we're not on last level. If
77 ! we are on last level, we do nothing and XUNDEF is left in POUT.
78 IF (lhook) CALL dr_hook('INTERPOL_SBL',0,zhook_handle)
79 pout(:) = xundef
80 ilevel=1
81 
82 !While there are XUNDEF values and we aren't at canopy's top
83 DO WHILE(any(pout(:)==xundef) .AND. ilevel/=SIZE(pz,2))
84 
85  !Where interpolation is needed and possible
86  !(10m is between ILEVEL and ILEVEL+1)
87  WHERE(pout(:)==xundef .AND. pz(:,ilevel+1)>=10.)
88 
89  !Interpolation between ILEVEL and ILEVEL+1
90  pout(:)=pin(:,ilevel) + &
91  (pin(:,ilevel+1)-pin(:,ilevel)) * &
92  (ph-pz(:,ilevel)) / (pz(:,ilevel+1)-pz(:,ilevel))
93 
94  END WHERE
95  ilevel=ilevel+1
96 END DO
97 IF (lhook) CALL dr_hook('INTERPOL_SBL',1,zhook_handle)
98 !
99 !-------------------------------------------------------------------------------
100 !
101 END SUBROUTINE interpol_sbl
subroutine interpol_sbl(PZ, PIN, PH, POUT)
Definition: interpol_sbl.F90:6