SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
surface_aero_cond.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_aero_cond(PRI, PZREF, PUREF, PVMOD, PZ0,&
7  pz0h, pac, pra, pch )
8 ! ######################################################################
9 !
10 !!**** *SURFACE_AERO_COND*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Computes the drag coefficients for heat and 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 !!
41 !!
42 !! REFERENCE
43 !! ---------
44 !!
45 !!
46 !! AUTHOR
47 !! ------
48 !!
49 !! V. Masson * Meteo-France *
50 !!
51 !! MODIFICATIONS
52 !! -------------
53 !! Original 20/01/98
54 !! 02/04/01 (P Jabouille) limitation of Z0 with 0.5 PUREF
55 !-------------------------------------------------------------------------------
56 !
57 !* 0. DECLARATIONS
58 ! ------------
59 !
60 USE modd_csts,ONLY : xkarman
61 USE modi_wind_threshold
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) :: pvmod ! module of the horizontal wind
75 REAL, DIMENSION(:), INTENT(IN) :: pzref ! reference height of the first
76  ! atmospheric level
77 REAL, DIMENSION(:), INTENT(IN) :: puref ! reference height of the wind
78  ! NOTE this is different from ZZREF
79  ! ONLY in stand-alone/forced mode,
80  ! NOT when coupled to a model (MesoNH)
81 REAL, DIMENSION(:), INTENT(IN) :: pz0 ! roughness length for momentum
82 REAL, DIMENSION(:), INTENT(IN) :: pz0h ! roughness length for heat
83 !
84 REAL, DIMENSION(:), INTENT(OUT) :: pac ! aerodynamical conductance
85 REAL, DIMENSION(:), INTENT(OUT) :: pra ! aerodynamical resistance
86 REAL, DIMENSION(:), INTENT(OUT) :: pch ! drag coefficient for heat
87 !
88 !* 0.2 declarations of local variables
89 !
90 !
91 REAL, DIMENSION(SIZE(PRI)) :: zz0, zz0h, zmu, &
92  zfh, zchstar, zph, zcdn, &
93  zsta, zdi, zwork1, zwork2, zwork3
94 REAL, DIMENSION(SIZE(PRI)) :: zvmod
95 !
96 INTEGER :: jj
97 REAL(KIND=JPRB) :: zhook_handle
98 !
99 ! Functions:
100 REAL :: x, chstar, ph
101  chstar(x) = 3.2165 + 4.3431*x + 0.5360*x*x - 0.0781*x*x*x
102 ph(x) = 0.5802 - 0.1571*x + 0.0327*x*x - 0.0026*x*x*x
103 !
104 !-------------------------------------------------------------------------------
105 !
106 !* 4. Surface aerodynamic resistance for heat transfers
107 ! -------------------------------------------------
108 !
109 IF (lhook) CALL dr_hook('SURFACE_AERO_COND',0,zhook_handle)
110 zvmod(:) = wind_threshold(pvmod(:),puref(:))
111 !
112 DO jj=1,SIZE(pri)
113 
114  zz0(jj) = min(pz0(jj),puref(jj)*0.5)
115  zz0h(jj) = min(zz0(jj),pz0h(jj))
116  zz0h(jj) = min(zz0h(jj),pzref(jj)*0.5)
117 !
118  zwork1(jj)=log( puref(jj)/zz0(jj) )
119  zwork2(jj)=pzref(jj)/zz0h(jj)
120  zwork3(jj)=zvmod(jj)*zvmod(jj)
121 
122  zmu(jj) = max( log( zz0(jj)/zz0h(jj) ), 0.0 )
123  zfh(jj) = zwork1(jj) / log(zwork2(jj))
124 !
125  zchstar(jj) = chstar(zmu(jj))
126  zph(jj) = ph(zmu(jj))
127 !
128 !
129  zcdn(jj) = (xkarman/zwork1(jj))**2.
130 !
131 !
132  zsta(jj) = pri(jj)*zwork3(jj)
133 !
134 !
135  IF ( pri(jj) < 0.0 ) THEN
136  zdi(jj) = 1. / ( zvmod(jj) &
137  +zchstar(jj)*zcdn(jj)*15. &
138  *zwork2(jj)**zph(jj) &
139  *zfh(jj) * sqrt(-zsta(jj)) &
140  )
141  pac(jj) = zcdn(jj)*(zvmod(jj)-15.* zsta(jj)*zdi(jj))*zfh(jj)
142 
143  ELSE
144  zdi(jj) = sqrt(zwork3(jj) + 5. * zsta(jj) )
145  pac(jj) = zcdn(jj)*zvmod(jj)/(1.+15.*zsta(jj)*zdi(jj) &
146  / zwork3(jj) /zvmod(jj) )*zfh(jj)
147  ENDIF
148 !
149  pra(jj) = 1. / pac(jj)
150 !
151  pch(jj) = 1. / (pra(jj) * zvmod(jj))
152 !
153 ENDDO
154 IF (lhook) CALL dr_hook('SURFACE_AERO_COND',1,zhook_handle)
155 !
156 !-------------------------------------------------------------------------------
157 !
158 END SUBROUTINE surface_aero_cond
real function, dimension(size(pwind)) wind_threshold(PWIND, PUREF)
subroutine surface_aero_cond(PRI, PZREF, PUREF, PVMOD, PZ0, PZ0H, PAC, PRA, PCH)