SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
surface_cd.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 surface_cd(PRI, PZREF, PUREF, PZ0EFF, PZ0H, &
7  pcd, pcdn)
8 ! #################################################################
9 !
10 !!**** *SURFACE_CD*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Computes the drag coefficients for momentum near the ground
16 !
17 !
18 !!** METHOD
19 !! ------
20 !
21 !
22 !
23 ! 1 and 2 : computation of relative humidity near the ground
24 !
25 ! 3 : richardson number
26 !
27 ! 4 : the aerodynamical resistance for heat transfers is deduced
28 !
29 ! 5 : the drag coefficient for momentum ZCD is computed
30 !
31 !
32 !! EXTERNAL
33 !! --------
34 !!
35 !!
36 !! IMPLICIT ARGUMENTS
37 !! ------------------
38 !!
39 !! MODD_CST
40 !! MODD_GROUND_PAR
41 !!
42 !!
43 !! REFERENCE
44 !! ---------
45 !!
46 !!
47 !! AUTHOR
48 !! ------
49 !!
50 !! V. Masson * Meteo-France *
51 !!
52 !! MODIFICATIONS
53 !! -------------
54 !! Original 20/01/98
55 !! 02/04/01 (P Jabouille) limitation of Z0 with 0.5 PUREF
56 !-------------------------------------------------------------------------------
57 !
58 !* 0. DECLARATIONS
59 ! ------------
60 !
61 USE modd_csts,ONLY : xkarman
62 !
63 USE mode_thermos
64 !
65 USE yomhook ,ONLY : lhook, dr_hook
66 USE parkind1 ,ONLY : jprb
67 !
68 IMPLICIT NONE
69 !
70 !* 0.1 declarations of arguments
71 !
72 !
73 REAL, DIMENSION(:), INTENT(IN) :: pri ! Richardson number
74 REAL, DIMENSION(:), INTENT(IN) :: pzref ! reference height of the first
75  ! atmospheric level
76 REAL, DIMENSION(:), INTENT(IN) :: puref ! reference height of the wind
77 ! ! NOTE this is different from ZZREF
78 ! ! ONLY in stand-alone/forced mode,
79 ! ! NOT when coupled to a model (MesoNH)
80 REAL, DIMENSION(:), INTENT(IN) :: pz0eff ! roughness length for momentum
81  ! with subgrid-scale orography
82 REAL, DIMENSION(:), INTENT(IN) :: pz0h ! roughness length for heat
83 !
84 REAL, DIMENSION(:), INTENT(OUT) :: pcd ! drag coefficient for momentum
85 REAL, DIMENSION(:), INTENT(OUT) :: pcdn ! neutral drag coefficient for momentum
86 !
87 !* 0.2 declarations of local variables
88 !
89 !
90 REAL :: zz0eff, zz0h, zmu, &
91  zcmstar, zpm, zcm, zfm
92 INTEGER :: jj
93 REAL(KIND=JPRB) :: zhook_handle
94 
95 ! Functions :
96 REAL :: x, cmstar, pm
97  cmstar(x) = 6.8741 + 2.6933*x - 0.3601*x*x + 0.0154*x*x*x
98 pm(x) = 0.5233 - 0.0815*x + 0.0135*x*x - 0.0010*x*x*x
99 
100 !-------------------------------------------------------------------------------
101 !
102 !* 1. Drag coefficient for momentum transfers
103 ! ---------------------------------------
104 !
105 
106 !
107 IF (lhook) CALL dr_hook('SURFACE_CD',0,zhook_handle)
108 DO jj=1,SIZE(pri)
109  zz0eff = min(pz0eff(jj),puref(jj)*0.5)
110  zz0h = min(zz0eff,pz0h(jj))
111 !
112  zmu = log( min(zz0eff/zz0h,200.) )
113 !
114  pcdn(jj) = (xkarman/log(puref(jj)/zz0eff))**2
115 
116  zcmstar = cmstar(zmu)
117  zpm = pm(zmu)
118 !
119  zcm = 10.*zcmstar*pcdn(jj)*( puref(jj)/zz0eff )**zpm
120 !
121  IF ( pri(jj) > 0.0 ) THEN
122  zfm = 1. + 10.*pri(jj) / sqrt( 1.+5.*pri(jj) )
123  zfm = 1. / zfm
124  ELSE
125  zfm = 1. - 10.*pri(jj) / ( 1.+zcm*sqrt(-pri(jj)) )
126  ENDIF
127 !
128  pcd(jj) = pcdn(jj)*zfm
129 !
130 ENDDO
131 IF (lhook) CALL dr_hook('SURFACE_CD',1,zhook_handle)
132 !
133 !-------------------------------------------------------------------------------
134 !
135 END SUBROUTINE surface_cd
subroutine surface_cd(PRI, PZREF, PUREF, PZ0EFF, PZ0H, PCD, PCDN)
Definition: surface_cd.F90:6