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