source: LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/calltherm.F90 @ 1294

Last change on this file since 1294 was 1294, checked in by Laurent Fairhead, 14 years ago

Modifications pour la nouvelle version des thermiques (2009/2010) CR et FH

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.5 KB
Line 
1!
2! $Header$
3!
4      subroutine calltherm(dtime  &
5     &      ,pplay,paprs,pphi,weak_inversion  &
6     &      ,u_seri,v_seri,t_seri,q_seri,zqsat,debut  &
7     &      ,d_u_ajs,d_v_ajs,d_t_ajs,d_q_ajs  &
8     &      ,fm_therm,entr_therm,detr_therm,zqasc,clwcon0,lmax,ratqscth,  &
9     &       ratqsdiff,zqsatth,Ale_bl,Alp_bl,lalim_conv,wght_th, &
10     &       zmax0,f0,zw2,fraca)
11
12      USE dimphy
13      implicit none
14#include "dimensions.h"
15!#include "dimphy.h"
16#include "thermcell.h"
17#include "iniprint.h"
18
19!IM 140508
20      INTEGER itap
21      REAL dtime
22      LOGICAL debut
23      LOGICAL logexpr0, logexpr2(klon,klev), logexpr1(klon)
24      REAL fact(klon)
25      INTEGER nbptspb
26
27      REAL u_seri(klon,klev),v_seri(klon,klev)
28      REAL t_seri(klon,klev),q_seri(klon,klev),qmemoire(klon,klev)
29      REAL weak_inversion(klon)
30      REAL paprs(klon,klev+1)
31      REAL pplay(klon,klev)
32      REAL pphi(klon,klev)
33      real zlev(klon,klev+1)
34!test: on sort lentr et a* pour alimenter KE
35      REAL wght_th(klon,klev)
36      INTEGER lalim_conv(klon)
37      REAL zw2(klon,klev+1),fraca(klon,klev+1)
38
39!FH Update Thermiques
40      REAL d_t_ajs(klon,klev), d_q_ajs(klon,klev)
41      REAL d_u_ajs(klon,klev),d_v_ajs(klon,klev)
42      real fm_therm(klon,klev+1)
43      real entr_therm(klon,klev),detr_therm(klon,klev)
44
45!********************************************************
46!     declarations
47      LOGICAL flag_bidouille_stratocu
48      real fmc_therm(klon,klev+1),zqasc(klon,klev)
49      real zqla(klon,klev)
50      real zqta(klon,klev)
51      real wmax_sec(klon)
52      real zmax_sec(klon)
53      real f_sec(klon)
54      real detrc_therm(klon,klev)
55! FH WARNING : il semble que ces save ne servent a rien
56!     save fmc_therm, detrc_therm
57      real clwcon0(klon,klev)
58      real zqsat(klon,klev)
59      real zw_sec(klon,klev+1)
60      integer lmix_sec(klon)
61      integer lmax(klon)
62      real ratqscth(klon,klev)
63      real ratqsdiff(klon,klev)
64      real zqsatth(klon,klev) 
65!nouvelles variables pour la convection
66      real Ale_bl(klon)
67      real Alp_bl(klon)
68      real Ale(klon)
69      real Alp(klon)
70!RC
71      !on garde le zmax du pas de temps precedent
72      real zmax0(klon), f0(klon)
73!********************************************************
74
75
76! variables locales
77      REAL d_t_the(klon,klev), d_q_the(klon,klev)
78      REAL d_u_the(klon,klev),d_v_the(klon,klev)
79!
80      real zfm_therm(klon,klev+1),zdt
81      real zentr_therm(klon,klev),zdetr_therm(klon,klev)
82! FH A VERIFIER : SAVE INUTILES
83!      save zentr_therm,zfm_therm
84
85      integer i,k
86      logical, save :: first=.true.
87!$OMP THREADPRIVATE(first)
88!********************************************************
89      if (first) then
90        itap=0
91        first=.false.
92      endif
93
94! Incrementer le compteur de la physique
95     itap   = itap + 1
96
97!  Modele du thermique
98!  ===================
99!         print*,'thermiques: WARNING on passe t au lieu de t_seri'
100
101
102! On prend comme valeur initiale des thermiques la valeur du pas
103! de temps precedent
104         zfm_therm(:,:)=fm_therm(:,:)
105         zdetr_therm(:,:)=detr_therm(:,:)
106         zentr_therm(:,:)=entr_therm(:,:)
107
108! On reinitialise les flux de masse a zero pour le cumul en
109! cas de splitting
110         fm_therm(:,:)=0.
111         entr_therm(:,:)=0.
112         detr_therm(:,:)=0.
113
114         Ale_bl(:)=0.
115         Alp_bl(:)=0.
116         if (prt_level.ge.10) then
117          print*,'thermV4 nsplit: ',nsplit_thermals,' weak_inversion'
118         endif
119
120!   tests sur les valeurs negatives de l'eau
121         logexpr0=prt_level.ge.10
122         nbptspb=0
123         do k=1,klev
124            do i=1,klon
125! Attention teste abderr 19-03-09
126!               logexpr2(i,k)=.not.q_seri(i,k).ge.0.
127                logexpr2(i,k)=.not.q_seri(i,k).ge.1.e-15
128               if (logexpr2(i,k)) then
129                q_seri(i,k)=1.e-15
130                nbptspb=nbptspb+1
131               endif
132!               if (logexpr0) &
133!    &             print*,'WARN eau<0 avant therm i=',i,'  k=',k  &
134!    &         ,' dq,q',d_q_the(i,k),q_seri(i,k)
135            enddo
136         enddo
137         if(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb   
138
139         zdt=dtime/float(nsplit_thermals)
140         do isplit=1,nsplit_thermals
141
142          if (iflag_thermals.eq.1) then
143            CALL thermcell_2002(klon,klev,zdt   &
144     &      ,pplay,paprs,pphi  &
145     &      ,u_seri,v_seri,t_seri,q_seri  &
146     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
147     &      ,zfm_therm,zentr_therm  &
148     &      ,r_aspect_thermals,30.,w2di_thermals  &
149     &      ,tau_thermals,3)
150          else if (iflag_thermals.eq.2) then
151            CALL thermcell_sec(klon,klev,zdt  &
152     &      ,pplay,paprs,pphi,zlev  &
153     &      ,u_seri,v_seri,t_seri,q_seri  &
154     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
155     &      ,zfm_therm,zentr_therm  &
156     &      ,r_aspect_thermals,30.,w2di_thermals  &
157     &      ,tau_thermals,3)
158          else if (iflag_thermals.eq.3) then
159            CALL thermcell(klon,klev,zdt  &
160     &      ,pplay,paprs,pphi  &
161     &      ,u_seri,v_seri,t_seri,q_seri  &
162     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
163     &      ,zfm_therm,zentr_therm  &
164     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
165     &      ,tau_thermals,3)
166          else if (iflag_thermals.eq.10) then
167            CALL thermcell_eau(klon,klev,zdt  &
168     &      ,pplay,paprs,pphi  &
169     &      ,u_seri,v_seri,t_seri,q_seri  &
170     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
171     &      ,zfm_therm,zentr_therm  &
172     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
173     &      ,tau_thermals,3)
174          else if (iflag_thermals.eq.11) then
175            stop 'cas non prevu dans calltherm'
176!           CALL thermcell_pluie(klon,klev,zdt  &
177!   &      ,pplay,paprs,pphi,zlev  &
178!    &      ,u_seri,v_seri,t_seri,q_seri  &
179!    &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
180!    &      ,zfm_therm,zentr_therm,zqla  &
181!    &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
182!    &      ,tau_thermals,3)
183          else if (iflag_thermals.eq.12) then
184            CALL calcul_sec(klon,klev,zdt  &
185     &      ,pplay,paprs,pphi,zlev  &
186     &      ,u_seri,v_seri,t_seri,q_seri  &
187     &      ,zmax_sec,wmax_sec,zw_sec,lmix_sec  &
188     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
189     &      ,tau_thermals)
190          else if (iflag_thermals==13.or.iflag_thermals==14) then
191            CALL thermcellV0_main(itap,klon,klev,zdt  &
192     &      ,pplay,paprs,pphi,debut  &
193     &      ,u_seri,v_seri,t_seri,q_seri  &
194     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
195     &      ,zfm_therm,zentr_therm,zdetr_therm,zqasc,zqla,lmax  &
196     &      ,ratqscth,ratqsdiff,zqsatth  &
197     &      ,r_aspect_thermals,l_mix_thermals  &
198     &      ,tau_thermals,Ale,Alp,lalim_conv,wght_th &
199     &      ,zmax0,f0,zw2,fraca)
200          else if (iflag_thermals==15.or.iflag_thermals==16) then
201            CALL thermcell_main(itap,klon,klev,zdt  &
202     &      ,pplay,paprs,pphi,debut  &
203     &      ,u_seri,v_seri,t_seri,q_seri  &
204     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
205     &      ,zfm_therm,zentr_therm,zdetr_therm,zqasc,zqla,lmax  &
206     &      ,ratqscth,ratqsdiff,zqsatth  &
207     &      ,r_aspect_thermals,l_mix_thermals  &
208     &      ,tau_thermals,Ale,Alp,lalim_conv,wght_th &
209     &      ,zmax0,f0,zw2,fraca)
210           if (prt_level.gt.10) write(lunout,*)'Apres thermcell_main OK'
211         else
212            STOP'Cas des thermiques non prevu'
213         endif
214
215       flag_bidouille_stratocu=iflag_thermals.lt.14.or.iflag_thermals.lt.16
216
217      fact(:)=0.
218      DO i=1,klon
219       logexpr1(i)=flag_bidouille_stratocu.or.weak_inversion(i).gt.0.5
220       IF(logexpr1(i)) fact(i)=1./float(nsplit_thermals)
221      ENDDO
222
223     DO k=1,klev
224!  transformation de la derivee en tendance
225            d_t_the(:,k)=d_t_the(:,k)*dtime*fact(:)
226            d_u_the(:,k)=d_u_the(:,k)*dtime*fact(:)
227            d_v_the(:,k)=d_v_the(:,k)*dtime*fact(:)
228            d_q_the(:,k)=d_q_the(:,k)*dtime*fact(:)
229            fm_therm(:,k)=fm_therm(:,k)  &
230     &      +zfm_therm(:,k)*fact(:)
231            entr_therm(:,k)=entr_therm(:,k)  &
232     &       +zentr_therm(:,k)*fact(:)
233            detr_therm(:,k)=detr_therm(:,k)  &
234     &       +zdetr_therm(:,k)*fact(:)
235      ENDDO
236       fm_therm(:,klev+1)=0.
237
238
239
240!  accumulation de la tendance
241            d_t_ajs(:,:)=d_t_ajs(:,:)+d_t_the(:,:)
242            d_u_ajs(:,:)=d_u_ajs(:,:)+d_u_the(:,:)
243            d_v_ajs(:,:)=d_v_ajs(:,:)+d_v_the(:,:)
244            d_q_ajs(:,:)=d_q_ajs(:,:)+d_q_the(:,:)
245
246!  incrementation des variables meteo
247            t_seri(:,:) = t_seri(:,:) + d_t_the(:,:)
248            u_seri(:,:) = u_seri(:,:) + d_u_the(:,:)
249            v_seri(:,:) = v_seri(:,:) + d_v_the(:,:)
250            qmemoire(:,:)=q_seri(:,:)
251            q_seri(:,:) = q_seri(:,:) + d_q_the(:,:)
252           if (prt_level.gt.10) write(lunout,*)'Apres apres thermcell_main OK'
253
254       DO i=1,klon
255        if(prt_level.GE.10) print*,'calltherm i Alp_bl Alp Ale_bl Ale',i,Alp_bl(i),Alp(i),Ale_bl(i),Ale(i)
256            fm_therm(i,klev+1)=0.
257            Ale_bl(i)=Ale_bl(i)+Ale(i)/float(nsplit_thermals)
258!            write(22,*)'ALE CALLTHERM',Ale_bl(i),Ale(i)
259            Alp_bl(i)=Alp_bl(i)+Alp(i)/float(nsplit_thermals)
260!            write(23,*)'ALP CALLTHERM',Alp_bl(i),Alp(i)
261       ENDDO
262
263!IM 060508 marche pas comme cela !!!        enddo ! isplit
264
265!   tests sur les valeurs negatives de l'eau
266         nbptspb=0
267            DO k = 1, klev
268            DO i = 1, klon
269               logexpr2(i,k)=.not.q_seri(i,k).ge.0.
270               if (logexpr2(i,k)) then
271                q_seri(i,k)=1.e-15
272                nbptspb=nbptspb+1
273!                if (prt_level.ge.10) then
274!                  print*,'WARN eau<0 apres therm i=',i,'  k=',k  &
275!    &         ,' dq,q',d_q_the(i,k),q_seri(i,k),  &
276!    &         'fm=',zfm_therm(i,k),'entr=',entr_therm(i,k)
277                 endif
278!       stop
279            ENDDO
280            ENDDO
281        IF(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb   
282! tests sur les valeurs de la temperature
283        nbptspb=0
284            DO k = 1, klev
285            DO i = 1, klon
286               logexpr2(i,k)=t_seri(i,k).lt.50..or.t_seri(i,k).gt.370.
287               if (logexpr2(i,k)) nbptspb=nbptspb+1
288!              if ((t_seri(i,k).lt.50.) .or.  &
289!    &              (t_seri(i,k).gt.370.)) then
290!                 print*,'WARN temp apres therm i=',i,'  k=',k  &
291!    &         ,' t_seri',t_seri(i,k)
292!              CALL abort
293!              endif
294            ENDDO
295            ENDDO
296        IF(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb
297         enddo ! isplit
298
299!
300!***************************************************************
301!     calcul du flux ascencant conservatif
302!            print*,'<<<<calcul flux ascendant conservatif'
303
304      fmc_therm=0.
305               do k=1,klev
306            do i=1,klon
307                  if (entr_therm(i,k).gt.0.) then
308                     fmc_therm(i,k+1)=fmc_therm(i,k)+entr_therm(i,k)
309                  else
310                     fmc_therm(i,k+1)=fmc_therm(i,k)
311                  endif
312                  detrc_therm(i,k)=(fmc_therm(i,k+1)-fm_therm(i,k+1))  &
313     &                 -(fmc_therm(i,k)-fm_therm(i,k))
314               enddo
315            enddo
316     
317     
318!****************************************************************
319!     calcul de l'humidite dans l'ascendance
320!      print*,'<<<<calcul de lhumidite dans thermique'
321!CR:on ne le calcule que pour le cas sec
322      if (iflag_thermals.le.11) then     
323      do i=1,klon
324         zqasc(i,1)=q_seri(i,1)
325         do k=2,klev
326            if (fmc_therm(i,k+1).gt.1.e-6) then
327               zqasc(i,k)=(fmc_therm(i,k)*zqasc(i,k-1)  &
328     &              +entr_therm(i,k)*q_seri(i,k))/fmc_therm(i,k+1)
329!CR:test on asseche le thermique
330!               zqasc(i,k)=zqasc(i,k)/2.
331!            else
332!               zqasc(i,k)=q_seri(i,k)
333            endif
334         enddo
335       enddo
336     
337
338!     calcul de l'eau condensee dans l'ascendance
339!             print*,'<<<<calcul de leau condensee dans thermique'
340             do i=1,klon
341                do k=1,klev
342                   clwcon0(i,k)=zqasc(i,k)-zqsat(i,k)
343                   if (clwcon0(i,k).lt.0. .or.   &
344     &             (fm_therm(i,k+1)+detrc_therm(i,k)).lt.1.e-6) then
345                      clwcon0(i,k)=0.
346                   endif
347                enddo
348             enddo
349       else
350              do i=1,klon
351                do k=1,klev
352                   clwcon0(i,k)=zqla(i,k) 
353                   if (clwcon0(i,k).lt.0. .or.   &
354     &             (fm_therm(i,k+1)+detrc_therm(i,k)).lt.1.e-6) then
355                   clwcon0(i,k)=0.
356                   endif
357                enddo
358             enddo
359       endif
360!*******************************************************************   
361
362
363      return
364
365      end
Note: See TracBrowser for help on using the repository browser.