SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mode_psychro.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 !##################
7 !##################
8 !
9 !!**** *MODE_PSYCHRO* -
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! NONE
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !!
24 !! AUTHOR
25 !! ------
26 !!
27 !!
28 !! MODIFICATIONS
29 !! -------------
30 !! Original 12/04/11
31 !! J.Escobar 11/13 : remove space in ELSEWHERE statement
32 !
33 USE yomhook ,ONLY : lhook, dr_hook
34 USE parkind1 ,ONLY : jprb
35 !
36 interface pe_from_pq
37  module procedure pe_from_pq_0d
38  module procedure pe_from_pq_1d
39 end interface
40 interface td_from_tq
41  module procedure td_from_tq_0d
42  module procedure td_from_tq_1d
43 end interface
44 interface rv_from_tptwb
45  module procedure rv_from_tptwb_0d
46  module procedure rv_from_tptwb_1d
47 end interface
48 interface twb_from_tpq
49  module procedure twb_from_tpq_0d
50  module procedure twb_from_tpq_1d
51 end interface
52 INTERFACE enth_fn_t_q
53  MODULE PROCEDURE enth_fn_t_q
54 END INTERFACE
55 INTERFACE q_fn_t_enth
56  MODULE PROCEDURE q_fn_t_enth
57 END INTERFACE
58 
59 contains
60 !PE_FROM_PQ
61 !----------
62 function pe_from_pq_0d(PP, PQ) RESULT(PE)
63 !arguments and result
64 REAL, INTENT(IN) :: pp !atmos. pressure (Pa)
65 REAL, INTENT(IN) :: pq !specific humidity (kg/kg)
66 REAL :: pe !water vapour pressure (Pa)
67 REAL(KIND=JPRB) :: zhook_handle
68 IF (lhook) CALL dr_hook('MODE_PSYCHRO:PE_FROM_PQ_0D',0,zhook_handle)
69 pe = pq * pp /(0.622 + 0.378 * pq)
70 IF (lhook) CALL dr_hook('MODE_PSYCHRO:PE_FROM_PQ_0D',1,zhook_handle)
71 end function pe_from_pq_0d
72 
73 function pe_from_pq_1d(PP, PQ) RESULT(PE)
74 !arguments and result
75 REAL, DIMENSION(:), INTENT(IN) :: pp !atmos. pressure (Pa)
76 REAL, DIMENSION(:), INTENT(IN) :: pq !specific humidity (kg/kg)
77 REAL, DIMENSION(SIZE(PQ)) :: pe !water vapour pressure (Pa)
78 REAL(KIND=JPRB) :: zhook_handle
79 IF (lhook) CALL dr_hook('MODE_PSYCHRO:PE_FROM_PQ_1D',0,zhook_handle)
80 pe(:) = pq(:) * pp(:) /(0.622 + 0.378 * pq(:))
81 IF (lhook) CALL dr_hook('MODE_PSYCHRO:PE_FROM_PQ_1D',1,zhook_handle)
82 end function pe_from_pq_1d
83 !-------------------------
84 
85 !TD_FROM_TQ
86 function td_from_tq_0d(PT, PQ) RESULT(PTD)
87 USE modd_csts
88 USE modd_surf_par, ONLY: xundef
89 !arguments and result
90 REAL, INTENT(IN) :: pt !Air Temp. (K)
91 REAL, INTENT(IN) :: pq !Specific humidity (kg/kg)
92 REAL :: ptd !Dew Point Air Temp. (K)
93 !local variables
94 REAL :: alpha
95 REAL :: zpe !water vapour pressure
96 REAL(KIND=JPRB) :: zhook_handle
97 
98 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TD_FROM_TQ_0D',0,zhook_handle)
99 zpe = pe_from_pq(pt, pq)
100 alpha = log(zpe/1000.)
101 IF (pt .GE. xtt .AND. pt .GE. 93.+xtt) THEN
102  ptd = xtt+6.54+14.526*alpha+0.7389*alpha*alpha+0.09486*alpha**3 &
103  +0.4569*(zpe/1000.)**0.1984
104 ELSE IF (pt .LT. xtt) THEN
105  ptd = xtt+6.09+12.608*alpha+0.4959*alpha*alpha
106 ELSE
107  ptd = xundef
108 ENDIF
109 ptd = min(ptd, pt)
110 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TD_FROM_TQ_0D',1,zhook_handle)
111 end function td_from_tq_0d
112 
113 function td_from_tq_1d(PT, PQ) RESULT(PTD)
114 USE modd_csts
115 USE modd_surf_par, ONLY: xundef
116 !arguments and result
117 REAL, DIMENSION(:), INTENT(IN) :: pt !Air Temp. (K)
118 REAL, DIMENSION(:), INTENT(IN) :: pq !Specific humidity (kg/kg)
119 REAL, DIMENSION(SIZE(PQ)) :: ptd !Dew Point Air Temp. (K)
120 !local variables
121 REAL, DIMENSION(SIZE(PQ)) :: alpha
122 REAL, DIMENSION(SIZE(PQ)) :: zpe !water vapour pressure
123 REAL(KIND=JPRB) :: zhook_handle
124 
125 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TD_FROM_TQ_1D',0,zhook_handle)
126 zpe = pe_from_pq(pt, pq)
127 alpha(:) = log(zpe(:)/1000.)
128 WHERE (pt .GE. xtt .AND. pt .GE. 93.+xtt)
129  ptd = xtt+6.54+14.526*alpha+0.7389*alpha*alpha+0.09486*alpha**3 &
130  +0.4569*(zpe/1000.)**0.1984
131  ELSEWHERE (pt .LT. xtt)
132  ptd = xtt+6.09+12.608*alpha+0.4959*alpha*alpha
133 ELSEWHERE
134  ptd = xundef
135 END WHERE
136 ptd(:) = min(ptd(:), pt(:))
137 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TD_FROM_TQ_1D',1,zhook_handle)
138 end function td_from_tq_1d
139 !-------------------------
140 
141 !RV_FROM_TPTWB
142 function rv_from_tptwb_0d(PT, PP, PTWB) RESULT(PRV)
143 USE mode_thermos
144 USE modd_csts
145 !arguments and result
146 REAL, INTENT(IN) :: pt !Air temperature (K)
147 REAL, INTENT(IN) :: pp !Atmos. Pressure (Pa)
148 REAL, INTENT(IN) :: ptwb !Wet Bulb Temp. (K)
149 REAL :: prv !water vapor mixing ratio (kg/kg)
150 REAL :: zrvsat !saturation water vapor mixing ratio
151 REAL(KIND=JPRB) :: zhook_handle
152 
153 IF (lhook) CALL dr_hook('MODE_PSYCHRO:RV_FROM_TPTWB_0D',0,zhook_handle)
154 zrvsat = qsat(pt, pp) / (1 - qsat(pt, pp))
155 prv = ((2501. - 2.326*(ptwb-xtt))*zrvsat - 1.006*(pt - ptwb)) &
156  / (2501. + 1.86*(pt - xtt) -4.186*(ptwb - xtt))
157 IF (lhook) CALL dr_hook('MODE_PSYCHRO:RV_FROM_TPTWB_0D',1,zhook_handle)
158 end function rv_from_tptwb_0d
159 
160 function rv_from_tptwb_1d(PT, PP, PTWB) RESULT(PRV)
161 USE mode_thermos
162 USE modd_csts
163 !arguments and result
164 REAL, DIMENSION(:), INTENT(IN) :: pt !Air temperature (K)
165 REAL, DIMENSION(:),INTENT(IN) :: pp !Atmos. Pressure (Pa)
166 REAL, DIMENSION(:),INTENT(IN) :: ptwb !Wet Bulb Temp. (K)
167 REAL, DIMENSION(SIZE(PT)) :: prv !water vapor mixing ratio (kg/kg)
168 REAL, DIMENSION(SIZE(PT)) :: zrvsat !saturation water vapor mixing ratio
169 REAL(KIND=JPRB) :: zhook_handle
170 
171 IF (lhook) CALL dr_hook('MODE_PSYCHRO:RV_FROM_TPTWB_1D',0,zhook_handle)
172 zrvsat = qsat(pt, pp) / (1 - qsat(pt, pp))
173 prv(:) = ((2501. - 2.326*(ptwb(:)-xtt))*zrvsat(:) - 1.006*(pt(:) - ptwb(:))) &
174  / (2501. + 1.86*(pt(:) - xtt) -4.186*(ptwb(:) - xtt))
175 IF (lhook) CALL dr_hook('MODE_PSYCHRO:RV_FROM_TPTWB_1D',1,zhook_handle)
176 end function rv_from_tptwb_1d
177 !----------------------------
178 
179 !TWB_FROM_TPQ
180 !------------
181 function twb_from_tpq_0d(PT, PP, PQ) RESULT(PTWB)
182 !arguments and results
183 REAL, INTENT(IN) :: pt !air temperature (K)
184 REAL, INTENT(IN) :: pq !mixing ratio (kg/kg)
185 REAL, INTENT(IN) :: pp !atmos. pressure (Pa)
186 REAL :: ptwb !Wet Bulb Temp. (K)
187 !local variable
188 REAL :: ztd !Dew Point Temp. (K)
189 REAL :: ztwbinf, ztwbsup, zrv
190 INTEGER :: jiter
191 REAL(KIND=JPRB) :: zhook_handle
192 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TWB_FROM_TPQ_0D',0,zhook_handle)
193 jiter = 1
194 ztd = td_from_tq(pt, pq)
195 !initial guess
196 ztwbsup = pt
197 ztwbinf = ztd
198 ptwb = 0.5 * (ztwbsup + ztwbinf)
199 DO WHILE (ztwbsup - ztwbinf > 0.001 .OR. jiter .LE. 50)
200  zrv = rv_from_tptwb(pt, pp, ptwb)
201  IF (zrv .GT. pq/(1 - pq)) THEN
202  ztwbsup = ptwb
203  ELSE
204  ztwbinf = ptwb
205  ENDIF
206  ptwb = 0.5 * (ztwbinf + ztwbsup)
207  jiter = jiter + 1
208 END DO
209 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TWB_FROM_TPQ_0D',1,zhook_handle)
210 end function twb_from_tpq_0d
211 
212 function twb_from_tpq_1d(PT, PP, PQ) RESULT(PTWB)
213 !arguments and results
214 REAL, DIMENSION(:), INTENT(IN) :: pt !air temperature (K)
215 REAL, DIMENSION(:), INTENT(IN) :: pq !humidity content (kg/kg)
216 REAL, DIMENSION(:), INTENT(IN) :: pp !atmos. pressure (Pa)
217 REAL, DIMENSION(SIZE(PT)) :: ptwb !Wet Bulb Temp. (K)
218 !local variable
219 REAL, DIMENSION(SIZE(PT)) :: ztd !Dew Point Temp. (K)
220 REAL, DIMENSION(SIZE(PT)) :: ztwbinf, ztwbsup, zrv
221 INTEGER :: jiter, ji
222 REAL(KIND=JPRB) :: zhook_handle
223 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TWB_FROM_TPQ_1D',0,zhook_handle)
224 ztd = td_from_tq(pt, pq)
225 !initial guess
226 ztwbsup = pt
227 ztwbinf = ztd
228 ptwb = 0.5 * (ztwbsup + ztwbinf)
229 DO ji=1,SIZE(pt)
230  jiter = 1
231  DO WHILE (ztwbsup(ji) - ztwbinf(ji) > 0.001 .OR. jiter .LE. 50)
232  zrv(ji) = rv_from_tptwb(pt(ji), pp(ji), ptwb(ji))
233  IF (zrv(ji) .GT. pq(ji)/(1 - pq(ji))) THEN
234  ztwbsup(ji) = ptwb(ji)
235  ELSE
236  ztwbinf(ji) = ptwb(ji)
237  ENDIF
238  ptwb(ji) = 0.5 * (ztwbinf(ji) + ztwbsup(ji))
239  END DO
240 END DO
241 IF (lhook) CALL dr_hook('MODE_PSYCHRO:TWB_FROM_TPQ_1D',1,zhook_handle)
242 end function twb_from_tpq_1d
243 !-------------------------------------------------------------------------------
244 !
245 ! ######################################
246  FUNCTION enth_fn_t_q(PT,PQ) RESULT(PENTH)
247 ! ######################################
248 !
249 !!
250 !! PURPOSE
251 !! -------
252 ! The purpose of this function is to compute the enthalpy function
253 ! of temperature and humidity content
254 !
255 !
256 !!** METHOD
257 !! ------
258 !!
259 !!
260 !! EXTERNAL
261 !! --------
262 !! NONE
263 !!
264 !! IMPLICIT ARGUMENTS
265 !! ------------------
266 !!
267 !! REFERENCE
268 !! ---------
269 !!
270 !!
271 !!
272 !! AUTHOR
273 !! ------
274 !!
275 !!
276 !! MODIFICATIONS
277 !! -------------
278 !! Original 12/04/11
279 !! A. Alias 01/2013 compi. on Bull : must be 1.0E-5 instead of 1.0D-5
280 !-------------------------------------------------------------------------------
281 !
282 !* 0. DECLARATIONS
283 ! ------------
284 !
285 IMPLICIT NONE
286 !
287 !* 0.1 Declarations of arguments and results
288 !
289 !
290 REAL, INTENT(IN) :: pt ! Temperature (K)
291 REAL, INTENT(IN) :: pq ! Humidity content (kg/kg)
292 REAL :: penth ! Enthalpy (J/kg)
293 !
294 !* 0.2 Declarations of local variables
295 !
296 REAL :: zt ! Temperature (C)
297 REAL :: zrv ! Mixing ratio (kg/kg_da)
298 REAL(KIND=JPRB) :: zhook_handle
299 !
300  IF (lhook) CALL dr_hook('MODE_PSYCHRO:ENTH_FN_T_Q',0,zhook_handle)
301 ! calculate enthalpy
302  zt = pt - 273.15
303  zrv=max(pq/(1-pq),1.0e-5)
304  penth=1.00484d3*zt+zrv*(2.50094d6+1.85895d3*zt)
305 !
306  IF (lhook) CALL dr_hook('MODE_PSYCHRO:ENTH_FN_T_Q',1,zhook_handle)
307 !-------------------------------------------------------------------------------
308 !
309 END FUNCTION enth_fn_t_q
310 !
311 !-------------------------------------------------------------------------------
312 !-------------------------------------------------------------------------------
313 !-------------------------------------------------------------------------------
314 !
315 ! ######################################
316  FUNCTION q_fn_t_enth(PT,PENTH) RESULT(PQ)
317 ! ######################################
318 !
319 !!
320 !! PURPOSE
321 !! -------
322 ! The purpose of this function is to compute the humidity content
323 ! as a function of temperature and enthalpy
324 !
325 !
326 !!** METHOD
327 !! ------
328 !!
329 !!
330 !! EXTERNAL
331 !! --------
332 !! NONE
333 !!
334 !! IMPLICIT ARGUMENTS
335 !! ------------------
336 !!
337 !! REFERENCE
338 !! ---------
339 !!
340 !!
341 !!
342 !! AUTHOR
343 !! ------
344 !!
345 !!
346 !! MODIFICATIONS
347 !! -------------
348 !! Original 12/04/11
349 !-------------------------------------------------------------------------------
350 !
351 !* 0. DECLARATIONS
352 ! ------------
353 !
354 IMPLICIT NONE
355 !
356 !* 0.1 Declarations of arguments and results
357 !
358 !
359 REAL, INTENT(IN) :: pt ! Temperature (K)
360 REAL, INTENT(IN) :: penth ! Enthalpy (J/kg)
361 REAL :: pq ! Humidity content (kg/kg)
362 !
363 !* 0.2 Declarations of local variables
364 !
365 REAL :: zt ! Temperature (C)
366 REAL :: zrv ! Mixing ratio (kg/kg_da)
367 REAL(KIND=JPRB) :: zhook_handle
368 !
369  IF (lhook) CALL dr_hook('MODE_PSYCHRO:Q_FN_T_ENTH',0,zhook_handle)
370 !
371  zt = pt - 273.15
372 !
373 ! calculate mixing ratio
374  zrv=(penth-1.00484d3*zt)/(2.50094d6+1.85895d3*zt)
375 !
376 ! validity test
377  IF (zrv < 0.0d0) THEN
378  zrv=1.d-5
379  ENDIF
380 !
381 ! calculate humidity content
382  pq = zrv/(1+zrv)
383 !
384  IF (lhook) CALL dr_hook('MODE_PSYCHRO:Q_FN_T_ENTH',1,zhook_handle)
385 !
386 !-------------------------------------------------------------------------------
387 !
388 END FUNCTION q_fn_t_enth
389 
390 END MODULE mode_psychro
real function, dimension(size(pt)) twb_from_tpq_1d(PT, PP, PQ)
real function, dimension(size(pt)) rv_from_tptwb_1d(PT, PP, PTWB)
real function td_from_tq_0d(PT, PQ)
real function, dimension(size(pq)) td_from_tq_1d(PT, PQ)
real function, dimension(size(pq)) pe_from_pq_1d(PP, PQ)
real function pe_from_pq_0d(PP, PQ)
real function rv_from_tptwb_0d(PT, PP, PTWB)
real function twb_from_tpq_0d(PT, PP, PQ)