SURFEX v8.1
General documentation of Surfex
water_flux.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 water_flux(PZ0SEA, &
7  PTA, PEXNA, PRHOA, PSST, PEXNS, PQA, PRR, PRS, &
8  PTT, PVMOD, PZREF, PUREF, &
9  PPS, OHANDLE_SIC, PQSAT, &
10  PSFTH, PSFTQ, PUSTAR, &
11  PCD, PCDN, PCH, PRI, PRESA, PZ0HSEA )
12 ! #######################################################################
13 !
14 !
15 !!**** *WATER_FLUX*
16 !!
17 !! PURPOSE
18 !! -------
19 ! Calculate the surface fluxes of heat, moisture, and momentum over
20 ! water surfaces.
21 !
22 !!** METHOD
23 !! ------
24 !
25 !! EXTERNAL
26 !! --------
27 !!
28 !! IMPLICIT ARGUMENTS
29 !! ------------------
30 !!
31 !!
32 !! REFERENCE
33 !! ---------
34 !!
35 !! AUTHOR
36 !! ------
37 !! S. Belair * Meteo-France *
38 !!
39 !! MODIFICATIONS
40 !! -------------
41 !! Original 01/09/95
42 !! (J.Stein) 16/11/95 use PUSLOPE and Theta to compute Ri
43 !! (P.Lacarrere) 19/03/96 bug in the ZTHVI and ZTHVIS computations
44 !! (J.Stein) 27/03/96 use only H and LE in the soil scheme
45 !! (P.Jabouille) 12/11/96 bug in the Z0 computation
46 !! (V.Masson) 01/02/00 detection of sea ice
47 !! (P. Tulet) 01/10/03 aerodynamical resistance output
48 !! (P. LeMoigne) 29/03/04 bug in the heat flux computation
49 !! (P. LeMoigne) 29/03/04 use z0h for diagnostics (ice)
50 !! (P. LeMoigne) 20/06/07 minimum wind speed and/or shear
51 !! B. Decharme 06/2009 limitation of Ri
52 !! B. Decharme 09/2012 limitation of Ri in surface_ri.F90
53 !! B. Decharme 06/2013 Charnock number according to coare3.0
54 !-------------------------------------------------------------------------------
55 !
56 !* 0. DECLARATIONS
57 ! ------------
58 !
59 USE modd_csts, ONLY : xg, xcpd, xlstt
60 USE modd_surf_par, ONLY : xundef
61 USE modd_snow_par, ONLY : xz0sn, xz0hsn
62 !
63 USE modi_surface_ri
64 USE modi_surface_aero_cond
65 USE modi_surface_cd
66 USE modi_surface_cdch_1darp
67 USE modi_wind_threshold
68 !
69 USE mode_thermos
70 !
73 !
74 USE modd_reprod_oper, ONLY : ccharnock
75 !
76 !
77 USE yomhook ,ONLY : lhook, dr_hook
78 USE parkind1 ,ONLY : jprb
79 !
80 IMPLICIT NONE
81 !
82 !* 0.1 declarations of arguments
83 !
84 !
85 REAL, DIMENSION(:), INTENT(IN) :: PTA ! air temperature at atm. level
86 REAL, DIMENSION(:), INTENT(IN) :: PQA ! air humidity at atm. level (kg/kg)
87 REAL, DIMENSION(:), INTENT(IN) :: PEXNA ! Exner function at atm. level
88 REAL, DIMENSION(:), INTENT(IN) :: PRHOA ! air density at atm. level
89 REAL, DIMENSION(:), INTENT(IN) :: PVMOD ! module of wind at atm. wind level
90 REAL, DIMENSION(:), INTENT(IN) :: PZREF ! atm. level for temp. and humidity
91 REAL, DIMENSION(:), INTENT(IN) :: PUREF ! atm. level for wind
92 REAL, DIMENSION(:), INTENT(IN) :: PSST ! Sea Surface Temperature
93 REAL, DIMENSION(:), INTENT(IN) :: PEXNS ! Exner function at sea surface
94 REAL, DIMENSION(:), INTENT(IN) :: PPS ! air pressure at sea surface
95 LOGICAL, INTENT(IN) :: OHANDLE_SIC ! if TRUE, do not care to detect seaice
96 REAL, DIMENSION(:), INTENT(IN) :: PRR ! rain rate
97 REAL, DIMENSION(:), INTENT(IN) :: PRS ! snow rate
98 REAL, INTENT(IN) :: PTT ! temperature of freezing point
99 !
100 REAL, DIMENSION(:), INTENT(INOUT) :: PZ0SEA! roughness length over the ocean
101 !
102 !
103 ! surface fluxes : latent heat, sensible heat, friction fluxes
104 REAL, DIMENSION(:), INTENT(OUT) :: PSFTH ! heat flux (W/m2)
105 REAL, DIMENSION(:), INTENT(OUT) :: PSFTQ ! water flux (kg/m2/s)
106 REAL, DIMENSION(:), INTENT(OUT) :: PUSTAR! friction velocity (m/s)
107 !
108 ! diagnostics
109 REAL, DIMENSION(:), INTENT(OUT) :: PQSAT ! humidity at saturation
110 REAL, DIMENSION(:), INTENT(OUT) :: PCD ! heat drag coefficient
111 REAL, DIMENSION(:), INTENT(OUT) :: PCDN ! momentum drag coefficient
112 REAL, DIMENSION(:), INTENT(OUT) :: PCH ! neutral momentum drag coefficient
113 REAL, DIMENSION(:), INTENT(OUT) :: PRI ! Richardson number
114 REAL, DIMENSION(:), INTENT(OUT) :: PRESA ! aerodynamical resistance
115 REAL, DIMENSION(:), INTENT(OUT) :: PZ0HSEA ! heat roughness length over the ocean
116 !
117 !
118 !* 0.2 declarations of local variables
119 !
120 !
121 REAL, DIMENSION(SIZE(PTA)) :: ZVMOD ! wind modulus
122 REAL, DIMENSION(SIZE(PTA)) :: ZUSTAR2 ! square of friction velocity
123 REAL, DIMENSION(SIZE(PTA)) :: ZAC ! Aerodynamical conductance
124 REAL, DIMENSION(SIZE(PTA)) :: ZRA ! Aerodynamical resistance
125 REAL, DIMENSION(SIZE(PTA)) :: ZDIRCOSZW ! orography slope cosine (=1 on water!)
126 REAL, DIMENSION(SIZE(PTA)) :: ZFP ! working variable
127 REAL, DIMENSION(SIZE(PTA)) :: ZRRCOR ! correction of CD, CH, CDN due to moist-gustiness
128 REAL, DIMENSION(SIZE(PTA)) :: ZCHARN ! Charnock number
129 !
130 REAL(KIND=JPRB) :: ZHOOK_HANDLE
131 !
132 !-------------------------------------------------------------------------------
133 !
134 ! 1. Initializations
135 ! ---------------
136 !
137 IF (lhook) CALL dr_hook('WATER_FLUX',0,zhook_handle)
138 zdircoszw=1.
139 !
140 pri(:) = xundef
141 pch(:) = xundef
142 pcd(:) = xundef
143 pcdn(:) = xundef
144 !
145 psfth(:)=xundef
146 psftq(:)=xundef
147 pustar(:)=xundef
148 presa(:)=xundef
149 !
150 !
151 ! 1.1 Saturated specified humidity near the water surface
152 ! ---------------------------------------------------
153 !
154 pqsat(:) = qsat(psst(:),pps(:))
155 !
156 !
157 ! 1.2 Wind speed threshold
158 ! --------------------
159 !
160 zvmod(:)=wind_threshold(pvmod(:),puref(:))
161 !
162 ! 1.3 Charnock number
163 ! ---------------
164 !
165 IF(ccharnock=='OLD')THEN
166  zcharn(:) = xvchrnk
167 ELSE
168 ! vary between 0.011 et 0.018 according to Chris Fairall's data as in coare3.0
169  zcharn(:) = max(0.011,min(0.018,0.011+0.007*(zvmod(:)-10.)/8.))
170 ENDIF
171 !
172 !-------------------------------------------------------------------------------
173 !
174 ! 2. Calculate the drag coefficient for momentum (PCD)
175 ! -------------------------------------------------
176 !
177 ! 2.1 Richardson number
178 ! -----------------
179 !
180  CALL surface_ri(psst,pqsat,pexns,pexna,pta,pqa, &
181  pzref, puref, zdircoszw,pvmod,pri)
182 !
183 ! 2.2 Detection of sea ice
184 ! --------------------
185 !
186 IF (lvziustar0_arp) THEN
187  pz0hsea(:)=min(pz0sea(:),pz0sea(:)*xrzhz0m)
188 ELSE
189  pz0hsea(:)=pz0sea(:)
190 ENDIF
191 !
192 IF (.NOT.ohandle_sic ) THEN
193  WHERE (psst(:) < ptt)
194  pz0hsea(:) = xz0hsn
195  END WHERE
196 ENDIF
197 !
198 ! 2.3 Drag coefficient
199 ! ----------------
200 !
201 IF (ldrag_coef_arp) THEN
202 
203  CALL surface_cdch_1darp(pzref, pz0sea, pz0hsea, zvmod, pta, psst, &
204  pqa, pqsat, pcd, pcdn, pch )
205 
206  zra(:) = 1. / ( pch(:) * zvmod(:) )
207 !
208 ELSE
209 !
210  CALL surface_cd(pri, pzref, puref, pz0sea, pz0hsea, pcd, pcdn)
211 !
212 ENDIF
213 !
214 !-------------------------------------------------------------------------------
215 !
216 ! 3. Calculate u* and the roughness length over the ocean
217 ! ----------------------------------------------------
218 !
219 ! According to Charnock's expression...
220 !
221 zustar2(:) = pcd(:)*zvmod(:)*zvmod(:)
222 !
223 pz0sea(:) = zcharn(:) * zustar2(:) / xg + xvz0cm * pcd(:) / pcdn(:)
224 !
225 IF (lvziustar0_arp .AND. xvziustar0>0.) THEN
226  pz0hsea(:)=pz0sea(:)*exp(-sqrt(zustar2(:))*xvziustar0)
227 ELSE
228  pz0hsea(:)=pz0sea(:)
229 ENDIF
230 !
231 IF (.NOT.ohandle_sic ) THEN
232  WHERE (psst(:) < ptt)
233  pz0sea(:) = xz0sn
234  END WHERE
235 ENDIF
236 !
237 !-------------------------------------------------------------------------------
238 !
239 ! 4. Drag coefficient for heat and aerodynamical resistance
240 ! -------------------------------------------------------
241 !
242 IF (.NOT.ldrag_coef_arp) THEN
243  CALL surface_aero_cond(pri, pzref, puref, zvmod, pz0sea, pz0hsea, zac, zra, pch)
244 ENDIF
245 !
246 IF (lrrgust_arp) THEN
247  zfp(:)=max(0.0,prr(:)+prs(:))
248  zrrcor(:)=sqrt(1.0+((((zfp(:)/(zfp(:)+xrrscale))**xrrgamma)*xutilgust)**2) &
249  /(pcd(:)*zvmod(:)**2))
250 
251  pcd = pcd*zrrcor
252  pch = pch*zrrcor
253  pcdn = pcdn*zrrcor
254 ENDIF
255 !
256 presa(:) = zra(:)
257 !
258 !-------------------------------------------------------------------------------
259 !
260 ! 5. The fluxes
261 ! ----------
262 !
263 psfth(:) = xcpd * prhoa(:) * pch(:) * zvmod(:) * ( psst(:) -pta(:) * pexns(:) / pexna(:) ) / pexns(:)
264 psftq(:) = prhoa(:) * pch(:) * zvmod(:) * ( pqsat(:)-pqa(:) )
265 pustar(:) = sqrt(zustar2(:))
266 !
267 IF (lhook) CALL dr_hook('WATER_FLUX',1,zhook_handle)
268 !
269 !-------------------------------------------------------------------------------
270 !
271 END SUBROUTINE water_flux
real, save xcpd
Definition: modd_csts.F90:63
real function, dimension(size(pwind)) wind_threshold(PWIND, PUREF)
subroutine surface_ri(PTG, PQS, PEXNS, PEXNA, PTA, PQA, PZREF, PUREF, PDIRCOSZW, PVMOD, PRI)
Definition: surface_ri.F90:8
character(len=3) ccharnock
logical lrrgust_arp
real, save xlstt
Definition: modd_csts.F90:71
real, parameter xundef
subroutine surface_aero_cond(PRI, PZREF, PUREF, PVMOD, PZ0, PZ0H, PAC, PRA, PCH)
subroutine water_flux(PZ0SEA,
Definition: water_flux.F90:7
real, save xg
Definition: modd_csts.F90:55
integer, parameter jprb
Definition: parkind1.F90:32
subroutine surface_cd(PRI, PZREF, PUREF, PZ0EFF, PZ0H, PCD, PCDN)
Definition: surface_cd.F90:8
logical lvziustar0_arp
logical lhook
Definition: yomhook.F90:15
subroutine surface_cdch_1darp(PZREF, PZ0EFF, PZ0H, PVMOD, PTA, PTG, PQA, PQS, PCD, PCDN, PCH)
logical ldrag_coef_arp