source: LMDZ6/branches/IPSL-CM6A-MR/libf/phylmd/stdlevvar_mod.F90 @ 3823

Last change on this file since 3823 was 3823, checked in by musat, 3 years ago

Nouveaux calculs a 2m et 10m

  • Property svn:executable set to *
File size: 24.8 KB
Line 
1!
2MODULE stdlevvar_mod
3!
4! This module contains main procedures for calculation
5! of temperature, specific humidity and wind at a reference level
6!
7  USE cdrag_mod
8  USE screenp_mod
9  USE screenc_mod
10  IMPLICIT NONE
11
12CONTAINS
13!
14!****************************************************************************************
15!
16!r original routine svn3623
17!
18      SUBROUTINE stdlevvar(klon, knon, nsrf, zxli, &
19                           u1, v1, t1, q1, z1, &
20                           ts1, qsurf, z0m, z0h, psol, pat1, &
21                           t_2m, q_2m, t_10m, q_10m, u_10m, ustar)
22      IMPLICIT NONE
23!-------------------------------------------------------------------------
24!
25! Objet : calcul de la temperature et l'humidite relative a 2m et du
26!         module du vent a 10m a partir des relations de Dyer-Businger et
27!         des equations de Louis.
28!
29! Reference : Hess, Colman et McAvaney (1995)       
30!
31! I. Musat, 01.07.2002
32!
33!AM On rajoute en sortie t et q a 10m pr le calcule d'hbtm2 dans clmain
34!
35!-------------------------------------------------------------------------
36!
37! klon----input-I- dimension de la grille physique (= nb_pts_latitude X nb_pts_longitude)
38! knon----input-I- nombre de points pour un type de surface
39! nsrf----input-I- indice pour le type de surface; voir indice_sol_mod.F90
40! zxli----input-L- TRUE si calcul des cdrags selon Laurent Li
41! u1------input-R- vent zonal au 1er niveau du modele
42! v1------input-R- vent meridien au 1er niveau du modele
43! t1------input-R- temperature de l'air au 1er niveau du modele
44! q1------input-R- humidite relative au 1er niveau du modele
45! z1------input-R- geopotentiel au 1er niveau du modele
46! ts1-----input-R- temperature de l'air a la surface
47! qsurf---input-R- humidite relative a la surface
48! z0m, z0h---input-R- rugosite
49! psol----input-R- pression au sol
50! pat1----input-R- pression au 1er niveau du modele
51!
52! t_2m---output-R- temperature de l'air a 2m
53! q_2m---output-R- humidite relative a 2m
54! u_10m--output-R- vitesse du vent a 10m
55!AM
56! t_10m--output-R- temperature de l'air a 10m
57! q_10m--output-R- humidite specifique a 10m
58! ustar--output-R- u*
59!
60      INTEGER, intent(in) :: klon, knon, nsrf
61      LOGICAL, intent(in) :: zxli
62      REAL, dimension(klon), intent(in) :: u1, v1, t1, q1, z1, ts1
63      REAL, dimension(klon), intent(in) :: qsurf, z0m, z0h
64      REAL, dimension(klon), intent(in) :: psol, pat1
65!
66      REAL, dimension(klon), intent(out) :: t_2m, q_2m, ustar
67      REAL, dimension(klon), intent(out) :: u_10m, t_10m, q_10m
68!-------------------------------------------------------------------------
69      include "flux_arp.h"
70      include "YOMCST.h"
71!IM PLUS
72      include "YOETHF.h"
73!
74! Quelques constantes et options:
75!
76! RKAR : constante de von Karman
77      REAL, PARAMETER :: RKAR=0.40
78! niter : nombre iterations calcul "corrector"
79!     INTEGER, parameter :: niter=6, ncon=niter-1
80      INTEGER, parameter :: niter=2, ncon=niter-1
81!
82! Variables locales
83      INTEGER :: i, n
84      REAL :: zref
85      REAL, dimension(klon) :: speed
86! tpot : temperature potentielle
87      REAL, dimension(klon) :: tpot
88      REAL, dimension(klon) :: zri1, cdran
89      REAL, dimension(klon) :: cdram, cdrah
90! ri1 : nb. de Richardson entre la surface --> la 1ere couche
91      REAL, dimension(klon) :: ri1
92      REAL, dimension(klon) :: testar, qstar
93      REAL, dimension(klon) :: zdte, zdq   
94! lmon : longueur de Monin-Obukhov selon Hess, Colman and McAvaney
95      DOUBLE PRECISION, dimension(klon) :: lmon
96      DOUBLE PRECISION, parameter :: eps=1.0D-20
97      REAL, dimension(klon) :: delu, delte, delq
98      REAL, dimension(klon) :: u_zref, te_zref, q_zref 
99      REAL, dimension(klon) :: temp, pref
100      LOGICAL :: okri
101      REAL, dimension(klon) :: u_zref_p, te_zref_p, temp_p, q_zref_p
102!convertgence
103      REAL, dimension(klon) :: te_zref_con, q_zref_con
104      REAL, dimension(klon) :: u_zref_c, te_zref_c, temp_c, q_zref_c
105      REAL, dimension(klon) :: ok_pred, ok_corr
106!     REAL, dimension(klon) :: conv_te, conv_q
107!-------------------------------------------------------------------------
108      DO i=1, knon
109       speed(i)=SQRT(u1(i)**2+v1(i)**2)
110       ri1(i) = 0.0
111      ENDDO
112!
113      okri=.FALSE.
114!      CALL coefcdrag(klon, knon, nsrf, zxli, &
115! &                   speed, t1, q1, z1, psol, &
116! &                   ts1, qsurf, rugos, okri, ri1,  &         
117! &                   cdram, cdrah, cdran, zri1, pref)           
118! Fuxing WANG, 04/03/2015, replace the coefcdrag by the merged version: cdrag
119
120      CALL cdrag(knon, nsrf, &
121 &                   speed, t1, q1, z1, &
122 &                   psol, ts1, qsurf, z0m, z0h, &
123 &                   cdram, cdrah, zri1, pref)
124
125! --- special Dice: on force cdragm ( a defaut de forcer ustar) MPL 05082013
126     IF (ok_prescr_ust) then
127      DO i = 1, knon
128       print *,'cdram avant=',cdram(i)
129       cdram(i) = ust*ust/speed(i)/speed(i)
130       print *,'cdram ust speed apres=',cdram(i),ust,speed
131      ENDDO
132     ENDIF
133!
134!---------Star variables----------------------------------------------------
135!
136      DO i = 1, knon
137        ri1(i) = zri1(i)
138        tpot(i) = t1(i)* (psol(i)/pat1(i))**RKAPPA
139        ustar(i) = sqrt(cdram(i) * speed(i) * speed(i))
140        zdte(i) = tpot(i) - ts1(i)
141        zdq(i) = max(q1(i),0.0) - max(qsurf(i),0.0)
142!
143!
144!IM BUG BUG BUG       zdte(i) = max(zdte(i),1.e-10)
145        zdte(i) = sign(max(abs(zdte(i)),1.e-10),zdte(i))
146!
147        testar(i) = (cdrah(i) * zdte(i) * speed(i))/ustar(i)
148        qstar(i) = (cdrah(i) * zdq(i) * speed(i))/ustar(i)
149        lmon(i) = (ustar(i) * ustar(i) * tpot(i))/ &
150 &                (RKAR * RG * testar(i))
151      ENDDO
152!
153!----------First aproximation of variables at zref --------------------------
154      zref = 2.0
155      CALL screenp(klon, knon, nsrf, speed, tpot, q1, &
156 &                 ts1, qsurf, z0m, lmon, &
157 &                 ustar, testar, qstar, zref, &
158 &                 delu, delte, delq)
159!
160      DO i = 1, knon
161        u_zref(i) = delu(i)
162        q_zref(i) = max(qsurf(i),0.0) + delq(i)
163        te_zref(i) = ts1(i) + delte(i)
164        temp(i) = te_zref(i) * (psol(i)/pat1(i))**(-RKAPPA)
165        q_zref_p(i) = q_zref(i)
166!       te_zref_p(i) = te_zref(i)
167        temp_p(i) = temp(i)
168      ENDDO
169!
170! Iteration of the variables at the reference level zref : corrector calculation ; see Hess & McAvaney, 1995
171!
172      DO n = 1, niter
173!
174        okri=.TRUE.
175        CALL screenc(klon, knon, nsrf, zxli, &
176 &                   u_zref, temp, q_zref, zref, &
177 &                   ts1, qsurf, z0m, z0h, psol, &           
178 &                   ustar, testar, qstar, okri, ri1, &
179 &                   pref, delu, delte, delq)
180!
181        DO i = 1, knon
182          u_zref(i) = delu(i)
183          q_zref(i) = delq(i) + max(qsurf(i),0.0)
184          te_zref(i) = delte(i) + ts1(i)
185!
186! return to normal temperature
187!
188          temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
189!         temp(i) = te_zref(i) - (zref* RG)/RCPD/ &
190!                 (1 + RVTMP2 * max(q_zref(i),0.0))
191!
192!IM +++
193!         IF(temp(i).GT.350.) THEN
194!           WRITE(*,*) 'temp(i) GT 350 K !!',i,nsrf,temp(i)
195!         ENDIF
196!IM ---
197!
198        IF(n.EQ.ncon) THEN
199          te_zref_con(i) = te_zref(i)
200          q_zref_con(i) = q_zref(i)
201        ENDIF
202!
203        ENDDO
204!
205      ENDDO
206!
207! verifier le critere de convergence : 0.25% pour te_zref et 5% pour qe_zref
208!
209!       DO i = 1, knon
210!         conv_te(i) = (te_zref(i) - te_zref_con(i))/te_zref_con(i)
211!         conv_q(i) = (q_zref(i) - q_zref_con(i))/q_zref_con(i)
212!IM +++
213!         IF(abs(conv_te(i)).GE.0.0025.AND.abs(conv_q(i)).GE.0.05) THEN
214!           PRINT*,'DIV','i=',i,te_zref_con(i),te_zref(i),conv_te(i), &
215!           q_zref_con(i),q_zref(i),conv_q(i)
216!         ENDIF
217!IM ---
218!       ENDDO
219!
220      DO i = 1, knon
221        q_zref_c(i) = q_zref(i)
222        temp_c(i) = temp(i)
223!
224!       IF(zri1(i).LT.0.) THEN
225!         IF(nsrf.EQ.1) THEN
226!           ok_pred(i)=1.
227!           ok_corr(i)=0.
228!         ELSE
229!           ok_pred(i)=0.
230!           ok_corr(i)=1.
231!         ENDIF
232!       ELSE
233!         ok_pred(i)=0.
234!         ok_corr(i)=1.
235!       ENDIF
236!
237        ok_pred(i)=0.
238        ok_corr(i)=1.
239!
240        t_2m(i) = temp_p(i) * ok_pred(i) + temp_c(i) * ok_corr(i)
241        q_2m(i) = q_zref_p(i) * ok_pred(i) + q_zref_c(i) * ok_corr(i)
242!IM +++
243!       IF(n.EQ.niter) THEN
244!       IF(t_2m(i).LT.t1(i).AND.t_2m(i).LT.ts1(i)) THEN
245!         PRINT*,' BAD t2m LT ',i,nsrf,t_2m(i),t1(i),ts1(i)
246!       ELSEIF(t_2m(i).GT.t1(i).AND.t_2m(i).GT.ts1(i)) THEN
247!         PRINT*,' BAD t2m GT ',i,nsrf,t_2m(i),t1(i),ts1(i)
248!       ENDIF
249!       ENDIF
250!IM ---
251      ENDDO
252!
253!
254!----------First aproximation of variables at zref --------------------------
255!
256      zref = 10.0
257      CALL screenp(klon, knon, nsrf, speed, tpot, q1, &
258 &                 ts1, qsurf, z0m, lmon, &
259 &                 ustar, testar, qstar, zref, &
260 &                 delu, delte, delq)
261!
262      DO i = 1, knon
263        u_zref(i) = delu(i)
264        q_zref(i) = max(qsurf(i),0.0) + delq(i)
265        te_zref(i) = ts1(i) + delte(i)
266        temp(i) = te_zref(i) * (psol(i)/pat1(i))**(-RKAPPA)
267!       temp(i) = te_zref(i) - (zref* RG)/RCPD/ &
268!                 (1 + RVTMP2 * max(q_zref(i),0.0))
269        u_zref_p(i) = u_zref(i)
270      ENDDO
271!
272! Iteration of the variables at the reference level zref : corrector ; see Hess & McAvaney, 1995
273!
274      DO n = 1, niter
275!
276        okri=.TRUE.
277        CALL screenc(klon, knon, nsrf, zxli, &
278 &                   u_zref, temp, q_zref, zref, &
279 &                   ts1, qsurf, z0m, z0h, psol, &
280 &                   ustar, testar, qstar, okri, ri1, &
281 &                   pref, delu, delte, delq)
282!
283        DO i = 1, knon
284          u_zref(i) = delu(i)
285          q_zref(i) = delq(i) + max(qsurf(i),0.0)
286          te_zref(i) = delte(i) + ts1(i)
287          temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
288!         temp(i) = te_zref(i) - (zref* RG)/RCPD/ &
289!                   (1 + RVTMP2 * max(q_zref(i),0.0))
290        ENDDO
291!
292      ENDDO
293!
294      DO i = 1, knon
295        u_zref_c(i) = u_zref(i)
296!
297        u_10m(i) = u_zref_p(i) * ok_pred(i) + u_zref_c(i) * ok_corr(i)
298!
299!AM
300        q_zref_c(i) = q_zref(i)
301        temp_c(i) = temp(i)
302        t_10m(i) = temp_p(i) * ok_pred(i) + temp_c(i) * ok_corr(i)
303        q_10m(i) = q_zref_p(i) * ok_pred(i) + q_zref_c(i) * ok_corr(i)
304!MA
305      ENDDO
306!
307      RETURN
308      END subroutine stdlevvar
309!
310      SUBROUTINE stdlevvarn(klon, knon, nsrf, zxli, &
311                           u1, v1, t1, q1, z1, &
312                           ts1, qsurf, z0m, z0h, psol, pat1, &
313                           t_2m, q_2m, t_10m, q_10m, u_10m, n2mout)
314!
315      USE ioipsl_getin_p_mod, ONLY : getin_p
316      IMPLICIT NONE
317!-------------------------------------------------------------------------
318!
319! Objet : calcul de la temperature et l'humidite relative a 2m et du
320!         module du vent a 10m a partir des relations de Dyer-Businger et
321!         des equations de Louis.
322!
323! Reference : Hess, Colman et McAvaney (1995)       
324!
325! I. Musat, 01.07.2002
326!
327!AM On rajoute en sortie t et q a 10m pr le calcule d'hbtm2 dans clmain
328!
329!-------------------------------------------------------------------------
330!
331! klon----input-I- dimension de la grille physique (= nb_pts_latitude X nb_pts_longitude)
332! knon----input-I- nombre de points pour un type de surface
333! nsrf----input-I- indice pour le type de surface; voir indice_sol_mod.F90
334! zxli----input-L- TRUE si calcul des cdrags selon Laurent Li
335! u1------input-R- vent zonal au 1er niveau du modele
336! v1------input-R- vent meridien au 1er niveau du modele
337! t1------input-R- temperature de l'air au 1er niveau du modele
338! q1------input-R- humidite relative au 1er niveau du modele
339! z1------input-R- geopotentiel au 1er niveau du modele
340! ts1-----input-R- temperature de l'air a la surface
341! qsurf---input-R- humidite relative a la surface
342! z0m, z0h---input-R- rugosite
343! psol----input-R- pression au sol
344! pat1----input-R- pression au 1er niveau du modele
345!
346! t_2m---output-R- temperature de l'air a 2m
347! q_2m---output-R- humidite relative a 2m
348! u_2m--output-R- vitesse du vent a 2m
349! u_10m--output-R- vitesse du vent a 10m
350!AM
351! t_10m--output-R- temperature de l'air a 10m
352! q_10m--output-R- humidite specifique a 10m
353!
354      INTEGER, intent(in) :: klon, knon, nsrf
355      LOGICAL, intent(in) :: zxli
356      REAL, dimension(klon), intent(in) :: u1, v1, t1, q1, z1, ts1
357      REAL, dimension(klon), intent(in) :: qsurf, z0m, z0h
358      REAL, dimension(klon), intent(in) :: psol, pat1
359!
360      REAL, dimension(klon), intent(out) :: t_2m, q_2m
361      REAL, dimension(klon), intent(out) :: u_10m, t_10m, q_10m
362      INTEGER, dimension(klon, 6), intent(out) :: n2mout
363!
364      REAL, dimension(klon) :: u_2m
365      REAL, dimension(klon) :: cdrm2m, cdrh2m, ri2m
366      REAL, dimension(klon) :: cdram, cdrah, zri1
367      REAL, dimension(klon) :: cdmn1, cdhn1, fm1, fh1
368      REAL, dimension(klon) :: cdmn2m, cdhn2m, fm2m, fh2m
369      REAL, dimension(klon) :: ri2m_new
370!-------------------------------------------------------------------------
371      include "flux_arp.h"
372      include "YOMCST.h"
373!IM PLUS
374      include "YOETHF.h"
375!
376! Quelques constantes et options:
377!
378! RKAR : constante de von Karman
379      REAL, PARAMETER :: RKAR=0.40
380! niter : nombre iterations calcul "corrector"
381!     INTEGER, parameter :: niter=6, ncon=niter-1
382!IM 071020     INTEGER, parameter :: niter=2, ncon=niter-1
383      INTEGER, parameter :: niter=2, ncon=niter
384!     INTEGER, parameter :: niter=6, ncon=niter
385!
386! Variables locales
387      INTEGER :: i, n
388      REAL :: zref
389      REAL, dimension(klon) :: speed
390! tpot : temperature potentielle
391      REAL, dimension(klon) :: tpot
392      REAL, dimension(klon) :: cdran
393! ri1 : nb. de Richardson entre la surface --> la 1ere couche
394      REAL, dimension(klon) :: ri1
395      DOUBLE PRECISION, parameter :: eps=1.0D-20
396      REAL, dimension(klon) :: delu, delte, delq
397      REAL, dimension(klon) :: delh, delm
398      REAL, dimension(klon) :: delh_new, delm_new
399      REAL, dimension(klon) :: u_zref, te_zref, q_zref 
400      REAL, dimension(klon) :: u_zref_pnew, te_zref_pnew, q_zref_pnew
401      REAL, dimension(klon) :: temp, pref
402      REAL, dimension(klon) :: temp_new, pref_new
403      LOGICAL :: okri
404      REAL, dimension(klon) :: u_zref_p, te_zref_p, temp_p, q_zref_p
405      REAL, dimension(klon) :: u_zref_p_new, te_zref_p_new, temp_p_new, q_zref_p_new
406!convergence
407      REAL, dimension(klon) :: te_zref_con, q_zref_con
408      REAL, dimension(klon) :: u_zref_c, te_zref_c, temp_c, q_zref_c
409      REAL, dimension(klon) :: ok_pred, ok_corr
410!
411      REAL, dimension(klon) :: cdrm10m, cdrh10m, ri10m
412      REAL, dimension(klon) :: cdmn10m, cdhn10m, fm10m, fh10m
413      REAL, dimension(klon) :: cdn2m, cdn1
414      REAL :: CEPDUE,zdu2
415      INTEGER :: nzref, nz1
416      LOGICAL, dimension(klon) :: ok_t2m_toosmall, ok_t2m_toobig
417      LOGICAL, dimension(klon) :: ok_q2m_toosmall, ok_q2m_toobig
418      LOGICAL, dimension(klon) :: ok_u2m_toobig
419      LOGICAL, dimension(klon) :: ok_t10m_toosmall, ok_t10m_toobig
420      LOGICAL, dimension(klon) :: ok_q10m_toosmall, ok_q10m_toobig
421      LOGICAL, dimension(klon) :: ok_u10m_toobig
422      INTEGER, dimension(klon, 6) :: n10mout
423
424!-------------------------------------------------------------------------
425      CEPDUE=0.1
426!
427! n2mout : compteur des pas de temps ou t2m,q2m ou u2m sont en dehors des intervalles
428!          [tsurf, temp], [qsurf, q1] ou [0, speed]
429!
430      n2mout(:,:)=0
431     
432      DO i=1, knon
433       speed(i)=MAX(SQRT(u1(i)**2+v1(i)**2),CEPDUE)
434       ri1(i) = 0.0
435      ENDDO
436!
437      okri=.FALSE.
438      CALL cdrag(knon, nsrf, &
439 &                   speed, t1, q1, z1, &
440 &                   psol, ts1, qsurf, z0m, z0h, &
441 &                   cdram, cdrah, zri1, pref)
442
443!
444      DO i = 1, knon
445        ri1(i) = zri1(i)
446        tpot(i) = t1(i)* (psol(i)/pat1(i))**RKAPPA
447        zdu2 = MAX(CEPDUE*CEPDUE, speed(i)**2)
448!
449      ENDDO
450!
451!----------First aproximation of variables at zref --------------------------
452      zref = 2.0
453!
454! calcul first-guess en utilisant dans les calculs à 2m
455! le Richardson de la premiere couche atmospherique
456!
457       CALL screencn(klon, knon, nsrf, zxli, &
458 &                   speed, tpot, q1, zref, &
459 &                   ts1, qsurf, z0m, z0h, psol, &           
460 &                   cdram, cdrah,  okri, &
461 &                   ri1, 1, &
462 &                   pref_new, delm_new, delh_new, ri2m)
463!
464       DO i = 1, knon
465         u_zref(i) = delm_new(i)*speed(i)
466         u_zref_p(i) = u_zref(i)
467         q_zref(i) = delh_new(i)*max(q1(i),0.0) + &
468         &           max(qsurf(i),0.0)*(1-delh_new(i))
469         q_zref_p(i) = q_zref(i)
470         te_zref(i) = delh_new(i)*tpot(i) + ts1(i)*(1-delh_new(i))
471         te_zref_p(i) = te_zref(i)
472!
473! return to normal temperature
474         temp(i) = te_zref(i) * (psol(i)/pref_new(i))**(-RKAPPA)
475         temp_p(i) = temp(i)
476!
477! compteurs ici
478!
479         ok_t2m_toosmall(i)=te_zref(i).LT.tpot(i).AND. &
480         & te_zref(i).LT.ts1(i)
481         ok_t2m_toobig(i)=te_zref(i).GT.tpot(i).AND. &
482         & te_zref(i).GT.ts1(i)
483         ok_q2m_toosmall(i)=q_zref(i).LT.q1(i).AND. &
484         & q_zref(i).LT.qsurf(i)
485         ok_q2m_toobig(i)=q_zref(i).GT.q1(i).AND. &
486         & q_zref(i).GT.qsurf(i)
487         ok_u2m_toobig(i)=u_zref(i).GT.speed(i)
488!
489         IF(ok_t2m_toosmall(i).OR.ok_t2m_toobig(i)) THEN
490             n2mout(i,1)=n2mout(i,1)+1
491         ENDIF
492         IF(ok_q2m_toosmall(i).OR.ok_q2m_toobig(i)) THEN
493             n2mout(i,3)=n2mout(i,3)+1
494         ENDIF
495         IF(ok_u2m_toobig(i)) THEN
496             n2mout(i,5)=n2mout(i,5)+1
497         ENDIF
498!
499         IF(ok_t2m_toosmall(i).OR.ok_t2m_toobig(i).OR. &
500          & ok_q2m_toosmall(i).OR.ok_q2m_toobig(i).OR. &
501          & ok_u2m_toobig(i)) THEN
502             delm_new(i)=min(max(delm_new(i),0.),1.)
503             delh_new(i)=min(max(delh_new(i),0.),1.)
504             u_zref(i) = delm_new(i)*speed(i)
505             u_zref_p(i) = u_zref(i)
506             q_zref(i) = delh_new(i)*max(q1(i),0.0) + &
507         &               max(qsurf(i),0.0)*(1-delh_new(i))
508             q_zref_p(i) = q_zref(i)
509             te_zref(i) = delh_new(i)*tpot(i) + ts1(i)*(1-delh_new(i))
510             te_zref_p(i) = te_zref(i)
511!
512! return to normal temperature
513             temp(i) = te_zref(i) * (psol(i)/pref_new(i))**(-RKAPPA)
514             temp_p(i) = temp(i)
515         ENDIF
516!
517       ENDDO
518!
519! Iteration of the variables at the reference level zref : corrector calculation ; see Hess & McAvaney, 1995
520!
521      DO n = 1, niter
522!
523        okri=.TRUE.
524        CALL screencn(klon, knon, nsrf, zxli, &
525 &                   u_zref, temp, q_zref, zref, &
526 &                   ts1, qsurf, z0m, z0h, psol, &
527 &                   cdram, cdrah,  okri, &
528 &                   ri1, 0, &
529 &                   pref, delm, delh, ri2m)
530!
531        DO i = 1, knon
532          u_zref(i) = delm(i)*speed(i)
533          q_zref(i) = delh(i)*max(q1(i),0.0) + &
534          &           max(qsurf(i),0.0)*(1-delh(i))
535          te_zref(i) = delh(i)*tpot(i) + ts1(i)*(1-delh(i))
536!
537! return to normal temperature
538          temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
539!
540! compteurs ici
541!
542          ok_t2m_toosmall(i)=te_zref(i).LT.tpot(i).AND. &
543          & te_zref(i).LT.ts1(i)
544          ok_t2m_toobig(i)=te_zref(i).GT.tpot(i).AND. &
545          & te_zref(i).GT.ts1(i)
546          ok_q2m_toosmall(i)=q_zref(i).LT.q1(i).AND. &
547          & q_zref(i).LT.qsurf(i)
548          ok_q2m_toobig(i)=q_zref(i).GT.q1(i).AND. &
549          & q_zref(i).GT.qsurf(i)
550          ok_u2m_toobig(i)=u_zref(i).GT.speed(i)
551!
552          IF(ok_t2m_toosmall(i).OR.ok_t2m_toobig(i)) THEN
553              n2mout(i,2)=n2mout(i,2)+1
554          ENDIF
555          IF(ok_q2m_toosmall(i).OR.ok_q2m_toobig(i)) THEN
556              n2mout(i,4)=n2mout(i,4)+1
557          ENDIF
558          IF(ok_u2m_toobig(i)) THEN
559              n2mout(i,6)=n2mout(i,6)+1
560          ENDIF
561!
562          IF(ok_t2m_toosmall(i).OR.ok_t2m_toobig(i).OR. &
563           & ok_q2m_toosmall(i).OR.ok_q2m_toobig(i).OR. &
564           & ok_u2m_toobig(i)) THEN
565              delm(i)=min(max(delm(i),0.),1.)
566              delh(i)=min(max(delh(i),0.),1.)
567              u_zref(i) = delm(i)*speed(i)
568              q_zref(i) = delh(i)*max(q1(i),0.0) + &
569          &           max(qsurf(i),0.0)*(1-delh(i))
570              te_zref(i) = delh(i)*tpot(i) + ts1(i)*(1-delh(i))
571              temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
572          ENDIF
573!
574!
575          IF(n.EQ.ncon) THEN
576            te_zref_con(i) = te_zref(i)
577            q_zref_con(i) = q_zref(i)
578          ENDIF
579!
580        ENDDO
581!
582      ENDDO
583!
584      DO i = 1, knon
585        q_zref_c(i) = q_zref(i)
586        temp_c(i) = temp(i)
587!
588        ok_pred(i)=0.
589        ok_corr(i)=1.
590!
591        t_2m(i) = temp_p(i) * ok_pred(i) + temp_c(i) * ok_corr(i)
592        q_2m(i) = q_zref_p(i) * ok_pred(i) + q_zref_c(i) * ok_corr(i)
593!
594        u_zref_c(i) = u_zref(i)
595        u_2m(i) = u_zref_p(i) * ok_pred(i) + u_zref_c(i) * ok_corr(i)
596      ENDDO
597!
598!
599!----------First aproximation of variables at zref --------------------------
600!
601      zref = 10.0
602!
603       CALL screencn(klon, knon, nsrf, zxli, &
604 &                   speed, tpot, q1, zref, &
605 &                   ts1, qsurf, z0m, z0h, psol, &           
606 &                   cdram, cdrah,  okri, &
607 &                   ri1, 1, &
608 &                   pref_new, delm_new, delh_new, ri10m)
609!
610       DO i = 1, knon
611         u_zref(i) = delm_new(i)*speed(i)
612         q_zref(i) = delh_new(i)*max(q1(i),0.0) + &
613         &           max(qsurf(i),0.0)*(1-delh_new(i))
614         te_zref(i) = delh_new(i)*tpot(i) + ts1(i)*(1-delh_new(i))
615         temp(i) = te_zref(i) * (psol(i)/pref_new(i))**(-RKAPPA)
616         u_zref_p(i) = u_zref(i)
617!
618! compteurs ici
619!
620         ok_t10m_toosmall(i)=te_zref(i).LT.tpot(i).AND. &
621         & te_zref(i).LT.ts1(i)
622         ok_t10m_toobig(i)=te_zref(i).GT.tpot(i).AND. &
623         & te_zref(i).GT.ts1(i)
624         ok_q10m_toosmall(i)=q_zref(i).LT.q1(i).AND. &
625         & q_zref(i).LT.qsurf(i)
626         ok_q10m_toobig(i)=q_zref(i).GT.q1(i).AND. &
627         & q_zref(i).GT.qsurf(i)
628         ok_u10m_toobig(i)=u_zref(i).GT.speed(i)
629!
630         IF(ok_t10m_toosmall(i).OR.ok_t10m_toobig(i).OR. &
631          & ok_q10m_toosmall(i).OR.ok_q10m_toobig(i).OR. &
632          & ok_u10m_toobig(i)) THEN
633             delm_new(i)=min(max(delm_new(i),0.),1.)
634             delh_new(i)=min(max(delh_new(i),0.),1.)
635             u_zref(i) = delm_new(i)*speed(i)
636             u_zref_p(i) = u_zref(i)
637             q_zref(i) = delh_new(i)*max(q1(i),0.0) + &
638         &               max(qsurf(i),0.0)*(1-delh_new(i))
639             te_zref(i) = delh_new(i)*tpot(i) + ts1(i)*(1-delh_new(i))
640             temp(i) = te_zref(i) * (psol(i)/pref_new(i))**(-RKAPPA)
641         ENDIF
642!
643       ENDDO
644!
645! Iteration of the variables at the reference level zref : corrector calculation ; see Hess & McAvaney, 1995
646!
647      DO n = 1, niter
648!
649        okri=.TRUE.
650        CALL screencn(klon, knon, nsrf, zxli, &
651 &                   u_zref, temp, q_zref, zref, &
652 &                   ts1, qsurf, z0m, z0h, psol, &
653 &                   cdram, cdrah,  okri, &
654 &                   ri1, 0, &
655 &                   pref, delm, delh, ri10m)
656!
657        DO i = 1, knon
658          u_zref(i) = delm(i)*speed(i)
659          q_zref(i) = delh(i)*max(q1(i),0.0) + &
660          &           max(qsurf(i),0.0)*(1-delh(i))
661          te_zref(i) = delh(i)*tpot(i) + ts1(i)*(1-delh(i))
662!
663! return to normal temperature
664          temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
665!
666! compteurs ici
667!
668          ok_t10m_toosmall(i)=te_zref(i).LT.tpot(i).AND. &
669          & te_zref(i).LT.ts1(i)
670          ok_t10m_toobig(i)=te_zref(i).GT.tpot(i).AND. &
671          & te_zref(i).GT.ts1(i)
672          ok_q10m_toosmall(i)=q_zref(i).LT.q1(i).AND. &
673          & q_zref(i).LT.qsurf(i)
674          ok_q10m_toobig(i)=q_zref(i).GT.q1(i).AND. &
675          & q_zref(i).GT.qsurf(i)
676          ok_u10m_toobig(i)=u_zref(i).GT.speed(i)
677!
678          IF(ok_t10m_toosmall(i).OR.ok_t10m_toobig(i)) THEN
679              n10mout(i,2)=n10mout(i,2)+1
680          ENDIF
681          IF(ok_q10m_toosmall(i).OR.ok_q10m_toobig(i)) THEN
682              n10mout(i,4)=n10mout(i,4)+1
683          ENDIF
684          IF(ok_u10m_toobig(i)) THEN
685              n10mout(i,6)=n10mout(i,6)+1
686          ENDIF
687!
688          IF(ok_t10m_toosmall(i).OR.ok_t10m_toobig(i).OR. &
689           & ok_q10m_toosmall(i).OR.ok_q10m_toobig(i).OR. &
690           & ok_u10m_toobig(i)) THEN
691              delm(i)=min(max(delm(i),0.),1.)
692              delh(i)=min(max(delh(i),0.),1.)
693              u_zref(i) = delm(i)*speed(i)
694              q_zref(i) = delh(i)*max(q1(i),0.0) + &
695          &           max(qsurf(i),0.0)*(1-delh(i))
696              te_zref(i) = delh(i)*tpot(i) + ts1(i)*(1-delh(i))
697              temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
698          ENDIF
699!
700!
701          IF(n.EQ.ncon) THEN
702            te_zref_con(i) = te_zref(i)
703            q_zref_con(i) = q_zref(i)
704          ENDIF
705!
706        ENDDO
707!
708      ENDDO
709!
710      DO i = 1, knon
711        q_zref_c(i) = q_zref(i)
712        temp_c(i) = temp(i)
713!
714        ok_pred(i)=0.
715        ok_corr(i)=1.
716!
717        t_10m(i) = temp_p(i) * ok_pred(i) + temp_c(i) * ok_corr(i)
718        q_10m(i) = q_zref_p(i) * ok_pred(i) + q_zref_c(i) * ok_corr(i)
719!
720        u_zref_c(i) = u_zref(i)
721        u_10m(i) = u_zref_p(i) * ok_pred(i) + u_zref_c(i) * ok_corr(i)
722      ENDDO
723!
724      RETURN
725      END subroutine stdlevvarn
726
727END MODULE stdlevvar_mod
Note: See TracBrowser for help on using the repository browser.