SURFEX v8.1
General documentation of Surfex
cls_wind.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 cls_wind( PZONA, PMERA, PHW, PCD, PCDN, PRI, PHV, PZON10M, PMER10M )
7 ! ###############################################################
8 !
9 !!**** *PARAMCLS*
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !
15 !
16 !!** METHOD
17 !! ------
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! none
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! USE MODD_CST
28 !! USE MODD_GROUND_PAR
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !!
35 !! AUTHOR
36 !! ------
37 !!
38 !!
39 !! MODIFICATIONS
40 !! -------------
41 !!
42 !! Original 26/10/98
43 !! S. Riette 06/2009 height of diagnostic becomes an argument
44 !! S. Riette 01/2010 XUNDEF is sent where forcing level is below heigt of
45 !! diagnostic (no extrapolation, only interpolation)
46 !! P. LeMoigne 02/2015 Suppress XUNDEF
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
52 USE modd_csts, ONLY : xkarman
53 USE modd_surf_par, ONLY : xundef
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 !
65 REAL, DIMENSION(:), INTENT(IN) :: PZONA ! zonal wind component
66 REAL, DIMENSION(:), INTENT(IN) :: PMERA ! meridian wind component
67 REAL, DIMENSION(:), INTENT(IN) :: PHW ! atmospheric level height (wind)
68 REAL, DIMENSION(:), INTENT(IN) :: PCD ! drag coefficient for momentum
69 REAL, DIMENSION(:), INTENT(IN) :: PCDN ! neutral drag coefficient
70 REAL, DIMENSION(:), INTENT(IN) :: PRI ! Richardson number
71 REAL, DIMENSION(:), INTENT(IN) :: PHV ! height of diagnostic (m)
72 !
73 REAL, DIMENSION(:), INTENT(OUT) :: PZON10M! zonal wind at 10 meters
74 REAL, DIMENSION(:), INTENT(OUT) :: PMER10M! meridian wind at 10 meters
75 !
76 !* 0.2 declarations of local variables
77 !
78 REAL, DIMENSION(SIZE(PHW)) :: ZBN,ZBD,ZRU
79 REAL, DIMENSION(SIZE(PHW)) :: ZLOGU,ZCORU,ZIV
80 REAL(KIND=JPRB) :: ZHOOK_HANDLE
81 !
82 !-------------------------------------------------------------------------------
83 !
84 IF (lhook) CALL dr_hook('CLS_WIND',0,zhook_handle)
85 pzon10m(:) = xundef
86 pmer10m(:) = xundef
87 !
88 zbn(:) = 0.
89 zbd(:) = 0.
90 zru(:) = 0.
91 zlogu(:) = 0.
92 zcoru(:) = 0.
93 ziv(:) = 0.
94 !
95 !* 1. preparatory calculations
96 ! ------------------------
97 !
98 zbn(:)=xkarman/sqrt(pcdn(:))
99 !
100 zbd(:)=xkarman/sqrt(pcd(:))
101 !
102 WHERE(phv(:)<=phw(:))
103  zru(:)=min(phv(:)/phw(:),1.)
104 ELSEWHERE
105  zru(:)=min(phw(:)/phv(:),1.)
106 END WHERE
107 !
108 zlogu(:)=log(1.+zru(:)*(exp(zbn(:)) -1.))
109 !
110 !* 2. Stability effects
111 ! -----------------
112 !
113 WHERE (pri(:)>=0.)
114  zcoru(:)=zru(:)*(zbn(:)-zbd(:))
115 END WHERE
116 !
117 WHERE (pri(:)< 0.)
118  zcoru(:)=log(1.+zru(:)*(exp(max(0.,zbn(:)-zbd(:)))-1.))
119 END WHERE
120 !
121 !* 3. Interpolation of dynamical variables
122 ! ------------------------------------
123 !
124 !
125 ziv(:)=max(0.,min(1.,(zlogu(:)-zcoru(:))/zbd(:)))
126 !
127 WHERE(phv(:)<=phw(:))
128  pzon10m(:)=pzona(:)*ziv(:)
129  pmer10m(:)=pmera(:)*ziv(:)
130 ELSEWHERE
131  pzon10m(:)=pzona(:)/max(1.,ziv(:))
132  pmer10m(:)=pmera(:)/max(1.,ziv(:))
133 END WHERE
134 IF (lhook) CALL dr_hook('CLS_WIND',1,zhook_handle)
135 !
136 !-------------------------------------------------------------------------------
137 !
138 END SUBROUTINE cls_wind
subroutine cls_wind(PZONA, PMERA, PHW, PCD, PCDN, PRI, PHV, PZON10M, PMER10M)
Definition: cls_wind.F90:7
real, save xkarman
Definition: modd_csts.F90:48
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15