source: trunk/LMDZ.GENERIC/libf/phystd/mass_redistribution_mod.F90 @ 3523

Last change on this file since 3523 was 2428, checked in by emillour, 4 years ago

Generci GCM:
Bug fix on mass_redistribution; argument rnat should be real, not integer.
Turned it into a mass_redistribution_mod module.
EM + YJ

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