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

Last change on this file since 2181 was 1943, checked in by idelkadi, 10 years ago

Changes concerinng the Hourdin et al. 2002 version of the thermals and
Ayotte cases

calltherm.F90


call to thermcell_2002 modified :
1) iflag_thermals changed from 1 to >= 1000 ; iflag_thermals-1000
controls sub options.
2) thermals w and fraction in output files.

hbtm.F


Singularity in the 1/heat dependency of the Monin Obukov length L when
heat=0. Since 1/L is used rather than L, it is preferable to compute
directly L. There is a dependency in 1/u* then which is treated with a
threshold value.
(+ some cleaning in the syntax).

lmdz1d.F


If nday<0, -nday is used as the total number of time steps of the
simulation.
The option with imposed wtsurf and wqsurf read in lmdz1d.def was not
active anymore.
< IF(.NOT.ok_flux_surf) THEN
changed to

IF(.NOT.ok_flux_surf.or.max(abs(wtsurf),abs(wqsurf))>0.) THEN

before

fsens=-wtsurf*rcpd*rho(1)
flat=-wqsurf*rlvtt*rho(1)

phys_output_write.F90 et phys_local_var_mod.F90


Removing the d_u_ajsb contribution to duthe (same for dv).
Those tendencies are not computed by the model ...
< zx_tmp_fi3d(1:klon,1:klev)=d_u_ajs(1:klon,1:klev)/pdtphys - &
< d_u_ajsb(1:klon,1:klev)/pdtphys
---

zx_tmp_fi3d(1:klon,1:klev)=d_u_ajs(1:klon,1:klev)/pdtphys

! d_u_ajsb(1:klon,1:klev)/pdtphys

thermcell_dq.F90, thermcell_main.F90


Some cleaning

thermcell_old.F


Control by iflag_thermals >= 1000
wa_moy and fraca in outputs
+ cleaning

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