source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/mass_redistribution.F90 @ 222

Last change on this file since 222 was 222, checked in by ymipsl, 10 years ago

Creating temporary dynamico/lmdz/saturn branche

YM

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