source: trunk/LMDZ.TITAN/libf/phytitan/mass_redistribution.F90 @ 3497

Last change on this file since 3497 was 1947, checked in by jvatant, 6 years ago

Enables altitude-depending gravity field g(z) (glat->gzlat) in physics
+ Can be dangerous ( disagreement with dyn) but important (compulsive !) to have correct altitudes in the chemistry
+ Can be activated with eff_gz flag in callphys.def
-- JVO

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