source: LMDZ5/trunk/libf/phylmd/calltherm.F90 @ 1786

Last change on this file since 1786 was 1785, checked in by Ehouarn Millour, 11 years ago

Transformation de l'include indicesol.h en un module indice_sol_mod et modification des appels dans tous les fichiers concernés.
Aucun changement des résultats ni des sorties du modèle vs 1784.
UG

...................................................

Replacement of the indicesol.h include by a module named indice_sol_mod. Modification of the calls in every affected files.
Results and outputs of simulations are unchanged in comparison with rev 1784.
UG

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 15.0 KB
Line 
1!
2! $Id: calltherm.F90 1785 2013-07-16 09:22:04Z idelkadi $
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,ztv,zpspsk,ztla,zthl &
11!!! nrlmd le 10/04/2012
12     &      ,pbl_tke,pctsrf,omega,airephy &
13     &      ,zlcl_th,fraca0,w0,w_conv,therm_tke_max0,env_tke_max0 &
14     &      ,n2,s2,ale_bl_stat &
15     &      ,therm_tke_max,env_tke_max &
16     &      ,alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke &
17     &      ,alp_bl_conv,alp_bl_stat &
18!!! fin nrlmd le 10/04/2012
19     &                    )
20
21      USE dimphy
22      USE indice_sol_mod
23      implicit none
24#include "dimensions.h"
25!#include "dimphy.h"
26#include "thermcell.h"
27#include "iniprint.h"
28
29
30!IM 140508
31      INTEGER, SAVE ::  itap
32!$OMP THREADPRIVATE(itap)
33      REAL dtime
34      LOGICAL debut
35      LOGICAL logexpr0, logexpr2(klon,klev), logexpr1(klon)
36      REAL fact(klon)
37      INTEGER nbptspb
38
39      REAL u_seri(klon,klev),v_seri(klon,klev)
40      REAL t_seri(klon,klev),q_seri(klon,klev),qmemoire(klon,klev)
41      REAL weak_inversion(klon)
42      REAL paprs(klon,klev+1)
43      REAL pplay(klon,klev)
44      REAL pphi(klon,klev)
45      real zlev(klon,klev+1)
46!test: on sort lentr et a* pour alimenter KE
47      REAL wght_th(klon,klev)
48      INTEGER lalim_conv(klon)
49      REAL zw2(klon,klev+1),fraca(klon,klev+1)
50
51!FH Update Thermiques
52      REAL d_t_ajs(klon,klev), d_q_ajs(klon,klev)
53      REAL d_u_ajs(klon,klev),d_v_ajs(klon,klev)
54      real fm_therm(klon,klev+1)
55      real entr_therm(klon,klev),detr_therm(klon,klev)
56
57!********************************************************
58!     declarations
59      LOGICAL flag_bidouille_stratocu
60      real fmc_therm(klon,klev+1),zqasc(klon,klev)
61      real zqla(klon,klev)
62      real zqta(klon,klev)
63      real ztv(klon,klev)
64      real zpspsk(klon,klev)
65      real ztla(klon,klev)
66      real zthl(klon,klev)
67      real wmax_sec(klon)
68      real zmax_sec(klon)
69      real f_sec(klon)
70      real detrc_therm(klon,klev)
71! FH WARNING : il semble que ces save ne servent a rien
72!     save fmc_therm, detrc_therm
73      real clwcon0(klon,klev)
74      real zqsat(klon,klev)
75      real zw_sec(klon,klev+1)
76      integer lmix_sec(klon)
77      integer lmax(klon)
78      real ratqscth(klon,klev)
79      real ratqsdiff(klon,klev)
80      real zqsatth(klon,klev) 
81!nouvelles variables pour la convection
82      real Ale_bl(klon)
83      real Alp_bl(klon)
84      real Ale(klon)
85      real Alp(klon)
86!RC
87      !on garde le zmax du pas de temps precedent
88      real zmax0(klon), f0(klon)
89
90!!! nrlmd le 10/04/2012
91      real pbl_tke(klon,klev+1,nbsrf)
92      real pctsrf(klon,nbsrf)
93      real omega(klon,klev)
94      real airephy(klon)
95      real zlcl_th(klon),fraca0(klon),w0(klon),w_conv(klon)
96      real therm_tke_max0(klon),env_tke_max0(klon)
97      real n2(klon),s2(klon)
98      real ale_bl_stat(klon)
99      real therm_tke_max(klon,klev),env_tke_max(klon,klev)
100      real alp_bl_det(klon),alp_bl_fluct_m(klon),alp_bl_fluct_tke(klon),alp_bl_conv(klon),alp_bl_stat(klon)
101!!! fin nrlmd le 10/04/2012
102
103!********************************************************
104
105
106! variables locales
107      REAL d_t_the(klon,klev), d_q_the(klon,klev)
108      REAL d_u_the(klon,klev),d_v_the(klon,klev)
109!
110      real zfm_therm(klon,klev+1),zdt
111      real zentr_therm(klon,klev),zdetr_therm(klon,klev)
112! FH A VERIFIER : SAVE INUTILES
113!      save zentr_therm,zfm_therm
114
115      character (len=20) :: modname='calltherm'
116      character (len=80) :: abort_message
117
118      integer i,k
119      logical, save :: first=.true.
120!$OMP THREADPRIVATE(first)
121!********************************************************
122      if (first) then
123        itap=0
124        first=.false.
125      endif
126
127! Incrementer le compteur de la physique
128     itap   = itap + 1
129
130!  Modele du thermique
131!  ===================
132!         print*,'thermiques: WARNING on passe t au lieu de t_seri'
133
134
135! On prend comme valeur initiale des thermiques la valeur du pas
136! de temps precedent
137         zfm_therm(:,:)=fm_therm(:,:)
138         zdetr_therm(:,:)=detr_therm(:,:)
139         zentr_therm(:,:)=entr_therm(:,:)
140
141! On reinitialise les flux de masse a zero pour le cumul en
142! cas de splitting
143         fm_therm(:,:)=0.
144         entr_therm(:,:)=0.
145         detr_therm(:,:)=0.
146
147         Ale_bl(:)=0.
148         Alp_bl(:)=0.
149         if (prt_level.ge.10) then
150          print*,'thermV4 nsplit: ',nsplit_thermals,' weak_inversion'
151         endif
152
153!   tests sur les valeurs negatives de l'eau
154         logexpr0=prt_level.ge.10
155         nbptspb=0
156         do k=1,klev
157            do i=1,klon
158! Attention teste abderr 19-03-09
159!               logexpr2(i,k)=.not.q_seri(i,k).ge.0.
160                logexpr2(i,k)=.not.q_seri(i,k).ge.1.e-15
161               if (logexpr2(i,k)) then
162                q_seri(i,k)=1.e-15
163                nbptspb=nbptspb+1
164               endif
165!               if (logexpr0) &
166!    &             print*,'WARN eau<0 avant therm i=',i,'  k=',k  &
167!    &         ,' dq,q',d_q_the(i,k),q_seri(i,k)
168            enddo
169         enddo
170         if(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb   
171
172         zdt=dtime/REAL(nsplit_thermals)
173         do isplit=1,nsplit_thermals
174
175          if (iflag_thermals.eq.1) then
176            CALL thermcell_2002(klon,klev,zdt   &
177     &      ,pplay,paprs,pphi  &
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  &
181     &      ,r_aspect_thermals,30.,w2di_thermals  &
182     &      ,tau_thermals)
183          else if (iflag_thermals.eq.2) then
184            CALL thermcell_sec(klon,klev,zdt  &
185     &      ,pplay,paprs,pphi,zlev  &
186     &      ,u_seri,v_seri,t_seri,q_seri  &
187     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
188     &      ,zfm_therm,zentr_therm  &
189     &      ,r_aspect_thermals,30.,w2di_thermals  &
190     &      ,tau_thermals)
191          else if (iflag_thermals.eq.3) then
192            CALL thermcell(klon,klev,zdt  &
193     &      ,pplay,paprs,pphi  &
194     &      ,u_seri,v_seri,t_seri,q_seri  &
195     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
196     &      ,zfm_therm,zentr_therm  &
197     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
198     &      ,tau_thermals)
199          else if (iflag_thermals.eq.10) then
200            CALL thermcell_eau(klon,klev,zdt  &
201     &      ,pplay,paprs,pphi  &
202     &      ,u_seri,v_seri,t_seri,q_seri  &
203     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
204     &      ,zfm_therm,zentr_therm  &
205     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
206     &      ,tau_thermals)
207          else if (iflag_thermals.eq.11) then
208              abort_message = 'cas non prevu dans calltherm'
209              CALL abort_gcm (modname,abort_message,1)
210
211!           CALL thermcell_pluie(klon,klev,zdt  &
212!   &      ,pplay,paprs,pphi,zlev  &
213!    &      ,u_seri,v_seri,t_seri,q_seri  &
214!    &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
215!    &      ,zfm_therm,zentr_therm,zqla  &
216!    &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
217!    &      ,tau_thermals,3)
218          else if (iflag_thermals.eq.12) then
219            CALL calcul_sec(klon,klev,zdt  &
220     &      ,pplay,paprs,pphi,zlev  &
221     &      ,u_seri,v_seri,t_seri,q_seri  &
222     &      ,zmax_sec,wmax_sec,zw_sec,lmix_sec  &
223     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
224     &      ,tau_thermals)
225          else if (iflag_thermals==13.or.iflag_thermals==14) then
226            CALL thermcellV0_main(itap,klon,klev,zdt  &
227     &      ,pplay,paprs,pphi,debut  &
228     &      ,u_seri,v_seri,t_seri,q_seri  &
229     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
230     &      ,zfm_therm,zentr_therm,zdetr_therm,zqasc,zqla,lmax  &
231     &      ,ratqscth,ratqsdiff,zqsatth  &
232     &      ,r_aspect_thermals,l_mix_thermals  &
233     &      ,tau_thermals,Ale,Alp,lalim_conv,wght_th &
234     &      ,zmax0,f0,zw2,fraca)
235          else if (iflag_thermals>=15.and.iflag_thermals<=18) then
236
237!            print*,'THERM iflag_thermas_ed=',iflag_thermals_ed
238            CALL thermcell_main(itap,klon,klev,zdt  &
239     &      ,pplay,paprs,pphi,debut  &
240     &      ,u_seri,v_seri,t_seri,q_seri  &
241     &      ,d_u_the,d_v_the,d_t_the,d_q_the  &
242     &      ,zfm_therm,zentr_therm,zdetr_therm,zqasc,zqla,lmax  &
243     &      ,ratqscth,ratqsdiff,zqsatth  &
244!    &      ,r_aspect_thermals,l_mix_thermals &
245!    &      ,tau_thermals,iflag_thermals_ed,iflag_coupl &
246     &      ,Ale,Alp,lalim_conv,wght_th &
247     &      ,zmax0,f0,zw2,fraca,ztv,zpspsk &
248     &      ,ztla,zthl &
249!!! nrlmd le 10/04/2012
250     &      ,pbl_tke,pctsrf,omega,airephy &
251     &      ,zlcl_th,fraca0,w0,w_conv,therm_tke_max0,env_tke_max0 &
252     &      ,n2,s2,ale_bl_stat &
253     &      ,therm_tke_max,env_tke_max &
254     &      ,alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke &
255     &      ,alp_bl_conv,alp_bl_stat &
256!!! fin nrlmd le 10/04/2012
257     &                         )
258           if (prt_level.gt.10) write(lunout,*)'Apres thermcell_main OK'
259         else
260           abort_message = 'Cas des thermiques non prevu'
261           CALL abort_gcm (modname,abort_message,1)
262         endif
263
264! Attention : les noms sont contre intuitif.
265! flag_bidouille_stratocu est .true. si on ne fait pas de bidouille.
266! Il aurait mieux valu avoir un nobidouille_stratocu
267! Et pour simplifier :
268! nobidouille_stratocu=.not.(iflag_thermals==13.or.iflag_thermals=15)
269! Ce serait bien de changer, mai en prenant le temps de vérifier que ca
270! fait bien ce qu'on croit.
271
272       flag_bidouille_stratocu=iflag_thermals<=12.or.iflag_thermals==14.or.iflag_thermals==16.or.iflag_thermals==18
273
274      if (iflag_thermals<=12) then
275         lmax=1
276         do k=1,klev-1
277            zdetr_therm(:,k)=zentr_therm(:,k)+zfm_therm(:,k)-zfm_therm(:,k+1)
278         enddo
279      endif
280
281      fact(:)=0.
282      DO i=1,klon
283       logexpr1(i)=flag_bidouille_stratocu.or.weak_inversion(i).gt.0.5
284       IF(logexpr1(i)) fact(i)=1./REAL(nsplit_thermals)
285      ENDDO
286
287     DO k=1,klev
288!  transformation de la derivee en tendance
289            d_t_the(:,k)=d_t_the(:,k)*dtime*fact(:)
290            d_u_the(:,k)=d_u_the(:,k)*dtime*fact(:)
291            d_v_the(:,k)=d_v_the(:,k)*dtime*fact(:)
292            d_q_the(:,k)=d_q_the(:,k)*dtime*fact(:)
293            fm_therm(:,k)=fm_therm(:,k)  &
294     &      +zfm_therm(:,k)*fact(:)
295            entr_therm(:,k)=entr_therm(:,k)  &
296     &       +zentr_therm(:,k)*fact(:)
297            detr_therm(:,k)=detr_therm(:,k)  &
298     &       +zdetr_therm(:,k)*fact(:)
299      ENDDO
300       fm_therm(:,klev+1)=0.
301
302
303
304!  accumulation de la tendance
305            d_t_ajs(:,:)=d_t_ajs(:,:)+d_t_the(:,:)
306            d_u_ajs(:,:)=d_u_ajs(:,:)+d_u_the(:,:)
307            d_v_ajs(:,:)=d_v_ajs(:,:)+d_v_the(:,:)
308            d_q_ajs(:,:)=d_q_ajs(:,:)+d_q_the(:,:)
309
310!  incrementation des variables meteo
311            t_seri(:,:) = t_seri(:,:) + d_t_the(:,:)
312            u_seri(:,:) = u_seri(:,:) + d_u_the(:,:)
313            v_seri(:,:) = v_seri(:,:) + d_v_the(:,:)
314            qmemoire(:,:)=q_seri(:,:)
315            q_seri(:,:) = q_seri(:,:) + d_q_the(:,:)
316           if (prt_level.gt.10) write(lunout,*)'Apres apres thermcell_main OK'
317
318       DO i=1,klon
319            fm_therm(i,klev+1)=0.
320            Ale_bl(i)=Ale_bl(i)+Ale(i)/REAL(nsplit_thermals)
321!            write(22,*)'ALE CALLTHERM',Ale_bl(i),Ale(i)
322            Alp_bl(i)=Alp_bl(i)+Alp(i)/REAL(nsplit_thermals)
323!            write(23,*)'ALP CALLTHERM',Alp_bl(i),Alp(i)
324        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)
325       ENDDO
326
327!IM 060508 marche pas comme cela !!!        enddo ! isplit
328
329!   tests sur les valeurs negatives de l'eau
330         nbptspb=0
331            DO k = 1, klev
332            DO i = 1, klon
333               logexpr2(i,k)=.not.q_seri(i,k).ge.0.
334               if (logexpr2(i,k)) then
335                q_seri(i,k)=1.e-15
336                nbptspb=nbptspb+1
337!                if (prt_level.ge.10) then
338!                  print*,'WARN eau<0 apres therm i=',i,'  k=',k  &
339!    &         ,' dq,q',d_q_the(i,k),q_seri(i,k),  &
340!    &         'fm=',zfm_therm(i,k),'entr=',entr_therm(i,k)
341                 endif
342            ENDDO
343            ENDDO
344        IF(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb   
345! tests sur les valeurs de la temperature
346        nbptspb=0
347            DO k = 1, klev
348            DO i = 1, klon
349               logexpr2(i,k)=t_seri(i,k).lt.50..or.t_seri(i,k).gt.370.
350               if (logexpr2(i,k)) nbptspb=nbptspb+1
351!              if ((t_seri(i,k).lt.50.) .or.  &
352!    &              (t_seri(i,k).gt.370.)) then
353!                 print*,'WARN temp apres therm i=',i,'  k=',k  &
354!    &         ,' t_seri',t_seri(i,k)
355!              CALL abort
356!              endif
357            ENDDO
358            ENDDO
359        IF(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb
360         enddo ! isplit
361
362!
363!***************************************************************
364!     calcul du flux ascencant conservatif
365!            print*,'<<<<calcul flux ascendant conservatif'
366
367      fmc_therm=0.
368               do k=1,klev
369            do i=1,klon
370                  if (entr_therm(i,k).gt.0.) then
371                     fmc_therm(i,k+1)=fmc_therm(i,k)+entr_therm(i,k)
372                  else
373                     fmc_therm(i,k+1)=fmc_therm(i,k)
374                  endif
375                  detrc_therm(i,k)=(fmc_therm(i,k+1)-fm_therm(i,k+1))  &
376     &                 -(fmc_therm(i,k)-fm_therm(i,k))
377               enddo
378            enddo
379     
380     
381!****************************************************************
382!     calcul de l'humidite dans l'ascendance
383!      print*,'<<<<calcul de lhumidite dans thermique'
384!CR:on ne le calcule que pour le cas sec
385      if (iflag_thermals.le.11) then     
386      do i=1,klon
387         zqasc(i,1)=q_seri(i,1)
388         do k=2,klev
389            if (fmc_therm(i,k+1).gt.1.e-6) then
390               zqasc(i,k)=(fmc_therm(i,k)*zqasc(i,k-1)  &
391     &              +entr_therm(i,k)*q_seri(i,k))/fmc_therm(i,k+1)
392!CR:test on asseche le thermique
393!               zqasc(i,k)=zqasc(i,k)/2.
394!            else
395!               zqasc(i,k)=q_seri(i,k)
396            endif
397         enddo
398       enddo
399     
400
401!     calcul de l'eau condensee dans l'ascendance
402!             print*,'<<<<calcul de leau condensee dans thermique'
403             do i=1,klon
404                do k=1,klev
405                   clwcon0(i,k)=zqasc(i,k)-zqsat(i,k)
406                   if (clwcon0(i,k).lt.0. .or.   &
407     &             (fm_therm(i,k+1)+detrc_therm(i,k)).lt.1.e-6) then
408                      clwcon0(i,k)=0.
409                   endif
410                enddo
411             enddo
412       else
413              do i=1,klon
414                do k=1,klev
415                   clwcon0(i,k)=zqla(i,k) 
416                   if (clwcon0(i,k).lt.0. .or.   &
417     &             (fm_therm(i,k+1)+detrc_therm(i,k)).lt.1.e-6) then
418                   clwcon0(i,k)=0.
419                   endif
420                enddo
421             enddo
422       endif
423!*******************************************************************   
424
425
426!jyg  Protection contre les temperatures nulles
427          do i=1,klon
428             do k=1,klev
429                if (ztla(i,k) .lt. 1.e-10) fraca(i,k) =0.
430             enddo
431          enddo
432
433
434      return
435
436      end
Note: See TracBrowser for help on using the repository browser.