source: trunk/LMDZ.GENERIC/libf/phystd/mass_redistribution.F90 @ 736

Last change on this file since 736 was 728, checked in by jleconte, 13 years ago

18/07/2012 == JL

  • New water cycle scheme:
    • largescale now in F90. Robustness increased by i) including evap inside largescale ii) computing the

condensed water amount iteratively

  • same improvements in moistadj.
  • Water thermodynamical data and saturation curves centralized in module watercommn_h
    • The saturation curves used are now Tetens formula as they are analyticaly inversible (Ts(P)-> Ps(T)).

New saturation curve yields very good agreement with the former one.

  • Saturation curves are now generalized for arbitrary water amount (not just q<<1)
  • The old watersat should be removed soon.
  • The effect of water vapor on total (surface) pressure can be taken into account by setting

mass_redistrib=.true. in callphys.def (routine mass_redistribution inspired from co2_condense in martian
model but with a different scheme as many routines evaporate/condense water vapor).

  • New cloud and precipitation scheme (JL + BC):
    • The default recovery assumption for computing the total cloud fraction has been changed (total random gave too

large cloud fractions). See totalcloudfrac.F90 for details and to change this.

  • Totalcloudfraction now set the total cloud fraction to the fraction of the

optically thickest cloud and totalcloudfrac is thus called in aeropacity.

  • Only the total cloud fraction is used to compute optical depth in aeropacity (no more effective

optical depth with exponential formula).

  • 4 precipitation schemes are now available (see rain.F90 for details). The choice can be made using precip_scheme

in callphys.def. Usage of the more physically based model of Boucher et al 95 (precip_scheme=4) is recommended.
default behavior is set to the former "simple scheme" (precip_scheme=1).

  • See rain.f90 to determine the parameter to be defined in callphys.def as a function of the precipitation scheme used.
  • Physiq.F90 now written in a matricial (more F90) way.
  • Radii (H2O and CO2 cloud particles, aerosols, duts, ...) calculations now centralized in module radii_mod.F90

and work with the new aerosol scheme implemented by Laura K. Some inconsistency may remain in callsedim.


Implementation compiled with ifort and pgf90.
gcm.e runs in Earth and Early Mars case with CO2 and H2O cycle + dust.

File size: 13.0 KB
Line 
1      SUBROUTINE mass_redistribution(ngrid,nlayer,nq,ptimestep,   &
2                       rnat,pcapcal,pplay,pplev,pt,ptsrf,pq,pqs,     &
3                       pu,pv,pdt,pdtsrf,pdq,pdu,pdv,pdmassmr,  &
4                       pdtmr,pdtsrfmr,pdpsrfmr,pdumr,pdvmr,pdqmr,pdqsmr)
5                                                   
6       USE watercommon_h, Only: Tsat_water,RLVTT
7
8       IMPLICIT NONE
9!=======================================================================
10!   subject:
11!   --------
12!     Mass and momentum fluxes through sigma levels as the surface pressure is modified are also taken into account
13!
14!   author:   Jeremy Leconte 2012 (from F.Forget 1998)
15!   ------
16!
17!   input:
18!   -----
19!    ngrid                 nombre de points de verticales
20!                          (toutes les boucles de la physique sont au
21!                          moins vectorisees sur ngrid)
22!    nlayer                nombre de couches
23!    pplay(ngrid,nlayer)   Pressure levels
24!    pplev(ngrid,nlayer+1) Pressure levels
25!    nq                    Number of tracers
26!
27!    pt(ngrid,nlayer)      temperature (en K)
28!    pq(ngrid,nlayer,nq)   tracer specific concentration (kg/kg of air)
29!    pu,pv (ngrid,nlayer)  wind velocity (m/s)
30!
31!                   
32!    pdX                   physical tendency of X before mass redistribution
33!
34!    pdmassmr                air Mass added to the atmosphere in each layer (kg/m2/s)
35!
36!   output:
37!   -------
38!
39!    pdXmr(ngrid)           physical tendency of X after mass redistribution
40!
41!   
42!
43!=======================================================================
44!
45!    0.  Declarations :
46!    ------------------
47!
48#include "dimensions.h"
49#include "dimphys.h"
50#include "comcstfi.h"
51#include "surfdat.h"
52#include "comgeomfi.h"
53#include "comvert.h"
54#include "paramet.h"
55#include "callkeys.h"
56#include "tracer.h"
57
58!-----------------------------------------------------------------------
59!    Arguments :
60!    ---------
61      INTEGER ngrid, nlayer, nq   
62      REAL ptimestep
63      REAL pcapcal(ngridmx)
64      INTEGER rnat(ngridmx)     
65      REAL pplay(ngrid,nlayer),pplev(ngrid,nlayer+1)
66      REAL pt(ngrid,nlayer),pdt(ngrid,nlayer)
67      REAL ptsrf(ngrid),pdtsrf(ngrid)
68      REAL pdtmr(ngrid,nlayer)
69      REAL pu(ngrid,nlayer) ,  pv(ngrid,nlayer)
70      REAL pdu(ngrid,nlayer) , pdv(ngrid,nlayer)
71      REAL pdmassmr(ngrid,nlayer)
72      REAL pdumr(ngrid,nlayer) , pdvmr(ngrid,nlayer)
73      REAL pq(ngridmx,nlayer,nq),pdq(ngrid,nlayer,nq)
74      REAL pqs(ngridmx,nq)
75      REAL pdqmr(ngrid,nlayer,nq),pdqsmr(ngrid,nq)
76      REAL pdpsrfmr(ngrid),pdtsrfmr(ngrid)
77!
78!    Local variables :
79!    -----------------
80
81!    Boiling/sublimation
82      REAL Tsat(ngridmx),zmassboil(ngridmx)
83
84!    vertical reorganization of sigma levels
85      REAL zzu(nlayermx),zzv(nlayermx)
86      REAL zzq(nlayermx,nq),zzt(nlayermx)
87!    Dummy variables     
88      INTEGER n,l,ig,iq
89      REAL zdtsig(ngridmx,nlayermx)
90      REAL zmass(ngridmx,nlayermx),zzmass(nlayermx),w(nlayermx+1)
91      REAL zdmass_sum(ngridmx,nlayermx+1)
92      REAL zmflux(nlayermx+1)
93      REAL zq1(nlayermx)
94      REAL ztsrf(ngridmx)
95      REAL ztm(nlayermx+1)
96      REAL zum(nlayermx+1) , zvm(nlayermx+1)
97      REAL zqm(nlayermx+1,nqmx),zqm1(nlayermx+1)
98
99!   local saved variables
100      LOGICAL, SAVE :: firstcall=.true.
101
102!----------------------------------------------------------------------
103
104!   Initialisation
105!   --------------
106!
107      IF (firstcall) THEN
108         firstcall=.false.       
109      ENDIF
110!
111!======================================================================
112!    Calcul of h2o condensation 
113!    ============================================================
114
115!    Used variable :
116!       pdmassmr      : air Mass added to the atmosphere in each layer per unit time (kg/m2/s)
117!       zdmass_sum(ngrid,l) : total air mass added to the atm above layer l per unit time (kg/m2/s)
118!
119!
120!     Surface tracer Tendencies set to 0
121!     -------------------------------------
122      pdqsmr(1:ngridmx,1:nqmx)=0.
123
124      ztsrf(1:ngridmx) = ptsrf(1:ngridmx) + pdtsrf(1:ngridmx)*ptimestep
125
126
127      DO ig=1,ngrid
128         zdmass_sum(ig,nlayermx+1)=0.
129         DO l = nlayermx, 1, -1
130           zmass(ig,l) = (pplev(ig,l)-pplev(ig,l+1))/g
131           zdmass_sum(ig,l)= zdmass_sum(ig,l+1)+pdmassmr(ig,l)
132         END DO
133      END DO
134
135
136      if (water) then
137         do ig=1,ngridmx
138            call Tsat_water(pplev(ig,1)+zdmass_sum(ig,1)*g*ptimestep,Tsat(ig))
139         enddo
140               call writediagfi(ngrid,'Tsat','saturation temperature at surface','',2,Tsat)
141         
142         do ig=1,ngridmx
143            if (ztsrf(ig).gt.Tsat(ig)) then
144               zmassboil(ig)=(ptsrf(ig)-Tsat(ig))*pcapcal(ig)/RLVTT/ptimestep
145               if ((zmassboil(ig)*ptimestep.gt.pqs(ig,igcm_h2o_vap)).and.(rnat(ig).eq.1)) then
146                  zmassboil(ig)=pqs(ig,igcm_h2o_vap)/ptimestep
147               endif
148               zmassboil(ig)=zmassboil(ig)*0.3 !momentary, should be 1. JL12
149               pdqsmr(ig,igcm_h2o_vap)=-zmassboil(ig)
150               pdtsrfmr(ig)=-zmassboil(ig)*RLVTT/pcapcal(ig)
151               ztsrf(ig)=ptsrf(ig)+pdtsrfmr(ig)*ptimestep
152            else
153               zmassboil(ig)=0.
154               pdtsrfmr(ig)=0.
155            endif
156         enddo
157      endif
158
159!     *************************
160!           UPDATE SURFACE
161!     *************************
162!    Changing pressure at the surface:
163!    """"""""""""""""""""""""""""""""""""
164         
165      pdpsrfmr(1:ngridmx) = (zdmass_sum(1:ngridmx,1)+zmassboil(1:ngridmx))*g
166
167      do ig = 1, ngridmx
168        IF(ABS(pdpsrfmr(ig)*ptimestep).GT.pplev(ig,1)) THEN
169         PRINT*,'STOP in condens'
170         PRINT*,'condensing more than total mass'
171         PRINT*,'Grid point ',ig
172         PRINT*,'Ps = ',pplev(ig,1)
173         PRINT*,'d Ps = ',pdpsrfmr(ig)*ptimestep
174         STOP
175        ENDIF
176      enddo ! of DO ig=1,ngrid
177
178
179! ***************************************************************
180!  Correction to account for redistribution between sigma or hybrid
181!  layers when changing surface pressure
182!  zzx quantities have dimension (nlayermx) to speed up calculation
183! *************************************************************
184
185      DO ig=1,ngrid
186         zzt(1:nlayermx)  = pt(ig,1:nlayermx) + pdt(ig,1:nlayermx) * ptimestep
187         zzu(1:nlayermx)  = pu(ig,1:nlayermx) + pdu(ig,1:nlayermx) * ptimestep
188         zzv(1:nlayermx)  = pv(ig,1:nlayermx) + pdv(ig,1:nlayermx) * ptimestep
189         zzq(1:nlayermx,1:nqmx)=pq(ig,1:nlayermx,1:nqmx)+pdq(ig,1:nlayermx,1:nqmx)*ptimestep ! must add the water that has fallen???
190
191!  Mass fluxes of air through the sigma levels (kg.m-2.s-1)  (>0 when up)
192!  """"""""""""""""""""""""""""""""""""""""""""""""""""""""""""""
193
194         zmflux(1) = zmassboil(ig)
195         DO l=1,nlayer
196            zmflux(l+1) = zmflux(l) + pdmassmr(ig,l) - (bp(l)-bp(l+1))*(zdmass_sum(ig,1)+zmflux(1))
197! zmflux set to 0 if very low to avoid: top layer is disappearing in v1ld 
198            if (abs(zmflux(l+1)).lt.1E-13.OR.bp(l+1).eq.0.) zmflux(l+1)=0.
199         END DO
200
201! Mass of each layer
202! ------------------
203         zzmass(1:nlayermx)=zmass(ig,1:nlayermx)*(1.+pdpsrfmr(ig)*ptimestep/pplev(ig,1))
204
205
206!  Corresponding fluxes for T,U,V,Q
207!  """"""""""""""""""""""""""""""""
208
209!        averaging operator for TRANSPORT 
210!        """"""""""""""""""""""""""""""""
211!        Value transfert at the surface interface when condensation
212!        sublimation:
213         ztm(1) = ztsrf(ig)
214         zum(1) = 0. 
215         zvm(1) = 0. 
216         zqm(1,1:nqmx)=0. ! most tracer do not condense !
217         if (water) zqm(1,igcm_h2o_vap)=1. ! flux is 100% h2o at surface
218         
219!        Van Leer scheme:
220         w(1:nlayermx+1)=-zmflux(1:nlayermx+1)*ptimestep
221         call vl1d(zzt,2.,zzmass,w,ztm)
222         call vl1d(zzu ,2.,zzmass,w,zum)
223         call vl1d(zzv ,2.,zzmass,w,zvm)
224         do iq=1,nqmx
225           zq1(1:nlayermx)=zzq(1:nlayermx,iq)
226           zqm1(1)=zqm(1,iq)
227!               print*,iq
228!               print*,zq1
229           call vl1d(zq1,2.,zzmass,w,zqm1)
230           do l=2,nlayer
231              zzq(l,iq)=zq1(l)
232              zqm(l,iq)=zqm1(l)
233           enddo
234         enddo
235
236!        Surface condensation affects low winds
237         if (zmflux(1).lt.0) then
238            zum(1)= zzu(1) *  (w(1)/zzmass(1))
239            zvm(1)= zzv(1) *  (w(1)/zzmass(1))
240            if (w(1).gt.zzmass(1)) then ! ensure numerical stability
241               zum(1)= (zzu(1)-zum(2))*zzmass(1)/w(1) + zum(2)
242               zvm(1)= (zzv(1)-zvm(2))*zzmass(1)/w(1) + zvm(2)
243            end if
244         end if
245                   
246         ztm(nlayer+1)= zzt(nlayer) ! should not be used, but...
247         zum(nlayer+1)= zzu(nlayer)  ! should not be used, but...
248         zvm(nlayer+1)= zzv(nlayer)  ! should not be used, but...
249         zqm(nlayer+1,1:nqmx)= zzq(nlayer,1:nqmx)
250 
251!        Tendencies on T, U, V, Q
252!        """"""""""""""""""""""""
253         DO l=1,nlayer
254 
255!           Tendencies on T
256            pdtmr(ig,l) = (1/zzmass(l)) *   &
257                (zmflux(l)*(ztm(l) - zzt(l))-zmflux(l+1)*(ztm(l+1)-zzt(l)))
258                  !JL12 the last term in Newcondens has been set to zero because we are only dealing with redistribution here
259
260!           Tendencies on U
261            pdumr(ig,l)   = (1/zzmass(l)) *( zmflux(l)*(zum(l) - zzu(l)) - zmflux(l+1)*(zum(l+1) - zzu(l)) )
262
263!           Tendencies on V
264            pdvmr(ig,l)   = (1/zzmass(l)) *( zmflux(l)*(zvm(l) - zzv(l)) - zmflux(l+1)*(zvm(l+1) - zzv(l)) )
265
266         END DO
267
268!        Tendencies on Q
269         do iq=1,nqmx
270            DO l=1,nlayer
271               pdqmr(ig,l,iq)= (1/zzmass(l)) *   &
272                   (zmflux(l)*(zqm(l,iq)-zzq(l,iq))- zmflux(l+1)*(zqm(l+1,iq)-zzq(l,iq)) - pdmassmr(ig,l)*zzq(l,iq))
273            END DO
274         enddo
275
276      END DO  ! loop on ig
277
278      return
279      end
280
281
282
283! *****************************************************************
284      SUBROUTINE vl1d(q,pente_max,zzmass,w,qm)
285!
286!   
287!     Operateur de moyenne inter-couche pour calcul de transport type
288!     Van-Leer " pseudo amont " dans la verticale
289!    q,w sont des arguments d'entree  pour le s-pg ....
290!    masse : masse de la couche Dp/g
291!    w : masse d'atm ``transferee'' a chaque pas de temps (kg.m-2)
292!    pente_max = 2 conseillee
293!
294!
295!   --------------------------------------------------------------------
296      IMPLICIT NONE
297
298#include "dimensions.h"
299
300!   Arguments:
301!   ----------
302      real zzmass(llm),pente_max
303      REAL q(llm),qm(llm+1)
304      REAL w(llm+1)
305!
306!      Local
307!   ---------
308!
309      INTEGER l
310!
311      real dzq(llm),dzqw(llm),adzqw(llm),dzqmax
312      real sigw, Mtot, MQtot
313      integer m
314!     integer ismax,ismin
315
316
317!    On oriente tout dans le sens de la pression
318!     W > 0 WHEN DOWN !!!!!!!!!!!!!
319
320      do l=2,llm
321            dzqw(l)=q(l-1)-q(l)
322            adzqw(l)=abs(dzqw(l))
323      enddo
324
325      do l=2,llm-1
326            if(dzqw(l)*dzqw(l+1).gt.0.) then
327                dzq(l)=0.5*(dzqw(l)+dzqw(l+1))
328            else
329                dzq(l)=0.
330            endif
331            dzqmax=pente_max*min(adzqw(l),adzqw(l+1))
332            dzq(l)=sign(min(abs(dzq(l)),dzqmax),dzq(l))
333      enddo
334
335         dzq(1)=0.
336         dzq(llm)=0.
337
338       do l = 1,llm-1
339
340!         Regular scheme (transfered mass < layer mass)
341!         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
342          if(w(l+1).gt.0. .and. w(l+1).le.zzmass(l+1)) then
343             sigw=w(l+1)/zzmass(l+1)
344             qm(l+1)=(q(l+1)+0.5*(1.-sigw)*dzq(l+1))
345          else if(w(l+1).le.0. .and. -w(l+1).le.zzmass(l)) then
346             sigw=w(l+1)/zzmass(l)
347             qm(l+1)=(q(l)-0.5*(1.+sigw)*dzq(l))
348
349!         Extended scheme (transfered mass > layer mass)
350!         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
351          else if(w(l+1).gt.0.) then
352             m=l+1
353             Mtot = zzmass(m)
354             MQtot = zzmass(m)*q(m)
355             do while ((m.lt.llm).and.(w(l+1).gt.(Mtot+zzmass(m+1))))
356                m=m+1
357                Mtot = Mtot + zzmass(m)
358                MQtot = MQtot + zzmass(m)*q(m)
359             end do
360             if (m.lt.llm) then
361                sigw=(w(l+1)-Mtot)/zzmass(m+1)
362                qm(l+1)= (1/w(l+1))*(MQtot + (w(l+1)-Mtot)*(q(m+1)+0.5*(1.-sigw)*dzq(m+1)) )
363             else
364!                w(l+1) = Mtot
365!                qm(l+1) = Mqtot / Mtot
366                write(*,*) 'top layer is disappearing !',l,Mtot,w(l+1),qm(l+1)
367                print*,zzmass
368                print*,w
369                print*,q
370                print*,qm
371               stop
372             end if
373          else      ! if(w(l+1).lt.0)
374             m = l-1
375             Mtot = zzmass(m+1)
376             MQtot = zzmass(m+1)*q(m+1)
377             if (m.gt.0) then ! because some compilers will have problems
378                              ! evaluating zzmass(0)
379              do while ((m.gt.0).and.(-w(l+1).gt.(Mtot+zzmass(m))))
380                m=m-1
381                Mtot = Mtot + zzmass(m+1)
382                MQtot = MQtot + zzmass(m+1)*q(m+1)
383                if (m.eq.0) exit
384              end do
385             endif
386             if (m.gt.0) then
387                sigw=(w(l+1)+Mtot)/zzmass(m)
388                qm(l+1)= (-1/w(l+1))*(MQtot + (-w(l+1)-Mtot)*(q(m)-0.5*(1.+sigw)*dzq(m))  )
389             else
390                qm(l+1)= (-1/w(l+1))*(MQtot + (-w(l+1)-Mtot)*qm(1))
391             end if   
392          end if
393       enddo
394
395!     boundary conditions (not used in newcondens !!)
396!         qm(llm+1)=0.
397!         if(w(1).gt.0.) then
398!            qm(1)=q(1)
399!         else
400!           qm(1)=0.
401!         end if
402
403      return
404      end
Note: See TracBrowser for help on using the repository browser.