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

Last change on this file since 1579 was 1542, checked in by emillour, 9 years ago

Generic GCM:

  • fix for 1D in writediagfi to enable writing at "ecritphy" rate.
  • move iniprint.h to "misc"
  • Some code cleanup in anticipation of future updates:
    • changed variable names in comgeomphy.F90: give them more explicit names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
    • removed long(), lati() and area() from comgeomfi_h.F90, use longitude(), latitude() and cell_are() from comgeomphy.F90 instead

EM

File size: 13.4 KB
Line 
1SUBROUTINE 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 tracer_h
10       USE planete_mod, only: bp
11       use comcstfi_mod, only: g
12       USE callkeys_mod, ONLY: water
13       
14       IMPLICIT NONE
15!=======================================================================
16!   subject:
17!   --------
18!     Mass and momentum fluxes through sigma levels as the surface pressure is modified are also taken into account
19!
20!   author:   Jeremy Leconte 2012 (from F.Forget 1998)
21!   ------
22!
23!   input:
24!   -----
25!    ngrid                 nombre de points de verticales
26!                          (toutes les boucles de la physique sont au
27!                          moins vectorisees sur ngrid)
28!    nlayer                nombre de couches
29!    pplay(ngrid,nlayer)   Pressure levels
30!    pplev(ngrid,nlayer+1) Pressure levels
31!    nq                    Number of tracers
32!
33!    pt(ngrid,nlayer)      temperature (en K)
34!    pq(ngrid,nlayer,nq)   tracer specific concentration (kg/kg of air)
35!    pu,pv (ngrid,nlayer)  wind velocity (m/s)
36!
37!                   
38!    pdX                   physical tendency of X before mass redistribution
39!
40!    pdmassmr                air Mass added to the atmosphere in each layer (kg/m2/s)
41!
42!   output:
43!   -------
44!
45!    pdXmr(ngrid)           physical tendency of X after mass redistribution
46!
47!   
48!
49!=======================================================================
50!
51!    0.  Declarations :
52!    ------------------
53
54!-----------------------------------------------------------------------
55!    Arguments :
56!    ---------
57      INTEGER ngrid, nlayer, nq   
58      REAL ptimestep
59      REAL pcapcal(ngrid)
60      INTEGER rnat(ngrid)     
61      REAL pplay(ngrid,nlayer),pplev(ngrid,nlayer+1)
62      REAL pt(ngrid,nlayer),pdt(ngrid,nlayer)
63      REAL ptsrf(ngrid),pdtsrf(ngrid)
64      REAL pdtmr(ngrid,nlayer)
65      REAL pu(ngrid,nlayer) ,  pv(ngrid,nlayer)
66      REAL pdu(ngrid,nlayer) , pdv(ngrid,nlayer)
67      REAL pdmassmr(ngrid,nlayer)
68      REAL pdumr(ngrid,nlayer) , pdvmr(ngrid,nlayer)
69      REAL pq(ngrid,nlayer,nq),pdq(ngrid,nlayer,nq)
70      REAL pqs(ngrid,nq)
71      REAL pdqmr(ngrid,nlayer,nq),pdqsmr(ngrid,nq)
72      REAL pdpsrfmr(ngrid),pdtsrfmr(ngrid)
73!
74!    Local variables :
75!    -----------------
76
77!    Boiling/sublimation
78      REAL Tsat(ngrid),zmassboil(ngrid)
79
80!    vertical reorganization of sigma levels
81      REAL zzu(nlayer),zzv(nlayer)
82      REAL zzq(nlayer,nq),zzt(nlayer)
83!    Dummy variables     
84      INTEGER n,l,ig,iq
85      REAL zdtsig(ngrid,nlayer)
86      REAL zmass(ngrid,nlayer),zzmass(nlayer),w(nlayer+1)
87      REAL zdmass_sum(ngrid,nlayer+1)
88      REAL zmflux(nlayer+1)
89      REAL zq1(nlayer)
90      REAL ztsrf(ngrid)
91      REAL ztm(nlayer+1)
92      REAL zum(nlayer+1) , zvm(nlayer+1)
93      REAL zqm(nlayer+1,nq),zqm1(nlayer+1)
94      REAL sigma(nlayer+1)
95
96!   local saved variables
97      LOGICAL, SAVE :: firstcall=.true.
98!$OMP THREADPRIVATE(firstcall)
99
100!----------------------------------------------------------------------
101
102!   Initialisation
103!   --------------
104!
105      IF (firstcall) THEN
106         firstcall=.false.       
107      ENDIF
108!
109!======================================================================
110!    Calcul of h2o condensation 
111!    ============================================================
112
113!    Used variable :
114!       pdmassmr      : air Mass added to the atmosphere in each layer per unit time (kg/m2/s)
115!       zdmass_sum(ngrid,l) : total air mass added to the atm above layer l per unit time (kg/m2/s)
116!
117!
118!     Surface tracer Tendencies set to 0
119!     -------------------------------------
120      pdqsmr(1:ngrid,1:nq)=0.
121
122      ztsrf(1:ngrid) = ptsrf(1:ngrid) + pdtsrf(1:ngrid)*ptimestep
123
124
125      DO ig=1,ngrid
126         zdmass_sum(ig,nlayer+1)=0.
127         DO l = nlayer, 1, -1
128           zmass(ig,l) = (pplev(ig,l)-pplev(ig,l+1))/glat(ig)
129           zdmass_sum(ig,l)= zdmass_sum(ig,l+1)+pdmassmr(ig,l)
130         END DO
131      END DO
132
133
134      if (water) then
135         do ig=1,ngrid
136            call Tsat_water(pplev(ig,1)+zdmass_sum(ig,1)*g*ptimestep,Tsat(ig))
137         enddo
138               call writediagfi(ngrid,'Tsat','saturation temperature at surface','',2,Tsat)
139         
140         do ig=1,ngrid
141            if (ztsrf(ig).gt.Tsat(ig)) then
142               zmassboil(ig)=(ptsrf(ig)-Tsat(ig))*pcapcal(ig)/RLVTT/ptimestep
143               if ((zmassboil(ig)*ptimestep.gt.pqs(ig,igcm_h2o_vap)).and.(rnat(ig).eq.1)) then
144                  zmassboil(ig)=pqs(ig,igcm_h2o_vap)/ptimestep
145               endif
146               zmassboil(ig)=zmassboil(ig)*0.0 !momentary, should be 1. JL12
147               pdqsmr(ig,igcm_h2o_vap)=-zmassboil(ig)
148               pdtsrfmr(ig)=-zmassboil(ig)*RLVTT/pcapcal(ig)
149               ztsrf(ig)=ptsrf(ig)+pdtsrfmr(ig)*ptimestep
150            else
151               zmassboil(ig)=0.
152               pdtsrfmr(ig)=0.
153            endif
154         enddo
155      endif
156
157!     *************************
158!           UPDATE SURFACE
159!     *************************
160!    Changing pressure at the surface:
161!    """"""""""""""""""""""""""""""""""""
162         
163      pdpsrfmr(1:ngrid) = (zdmass_sum(1:ngrid,1)+zmassboil(1:ngrid))*g
164
165      do ig = 1, ngrid
166        IF(ABS(pdpsrfmr(ig)*ptimestep).GT.pplev(ig,1)) THEN
167         PRINT*,'STOP in condens in mass_redistribution'
168         PRINT*,'condensing more than total mass'
169         PRINT*,'Grid point ',ig
170         PRINT*,'Ps = ',pplev(ig,1)
171         PRINT*,'d Ps = ',pdpsrfmr(ig)*ptimestep
172         STOP
173        ENDIF
174      enddo ! of DO ig=1,ngrid
175
176
177! ***************************************************************
178!  Correction to account for redistribution between sigma or hybrid
179!  layers when changing surface pressure
180!  zzx quantities have dimension (nlayer) to speed up calculation
181! *************************************************************
182
183      DO ig=1,ngrid
184         zzt(1:nlayer)  = pt(ig,1:nlayer) + pdt(ig,1:nlayer) * ptimestep
185         zzu(1:nlayer)  = pu(ig,1:nlayer) + pdu(ig,1:nlayer) * ptimestep
186         zzv(1:nlayer)  = pv(ig,1:nlayer) + pdv(ig,1:nlayer) * ptimestep
187         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???
188
189!  Mass fluxes of air through the sigma levels (kg.m-2.s-1)  (>0 when up)
190!  """"""""""""""""""""""""""""""""""""""""""""""""""""""""""""""
191         zmflux(1) = zmassboil(ig)
192         sigma(1)=1
193         DO l=1,nlayer
194           ! Ehouarn: shouldn't we rather compute sigma levels than use bp()?
195!           sigma(l+1)=pplev(ig,l+1)/pplev(ig,1)
196!           zmflux(l+1) = zmflux(l) + pdmassmr(ig,l) - &
197!                        (sigma(l)-sigma(l+1))*(zdmass_sum(ig,1)+zmflux(1))
198!            if (abs(zmflux(l+1)).lt.1E-13.OR.sigma(l+1).eq.0.) zmflux(l+1)=0.
199           ! Ehouarn: but for now leave things as before
200            zmflux(l+1) = zmflux(l) + pdmassmr(ig,l) - (bp(l)-bp(l+1))*(zdmass_sum(ig,1)+zmflux(1))
201! zmflux set to 0 if very low to avoid: top layer is disappearing in v1ld 
202            if (abs(zmflux(l+1)).lt.1E-13.OR.bp(l+1).eq.0.) zmflux(l+1)=0.
203         END DO
204
205! Mass of each layer
206! ------------------
207         zzmass(1:nlayer)=zmass(ig,1:nlayer)*(1.+pdpsrfmr(ig)*ptimestep/pplev(ig,1))
208
209
210!  Corresponding fluxes for T,U,V,Q
211!  """"""""""""""""""""""""""""""""
212
213!        averaging operator for TRANSPORT 
214!        """"""""""""""""""""""""""""""""
215!        Value transfert at the surface interface when condensation
216!        sublimation:
217         ztm(1) = ztsrf(ig)
218         zum(1) = 0. 
219         zvm(1) = 0. 
220         zqm(1,1:nq)=0. ! most tracer do not condense !
221         if (water) zqm(1,igcm_h2o_vap)=1. ! flux is 100% h2o at surface
222         
223!        Van Leer scheme:
224         w(1:nlayer+1)=-zmflux(1:nlayer+1)*ptimestep
225         call vl1d(nlayer,zzt,2.,zzmass,w,ztm)
226         call vl1d(nlayer,zzu,2.,zzmass,w,zum)
227         call vl1d(nlayer,zzv,2.,zzmass,w,zvm)
228         do iq=1,nq
229           zq1(1:nlayer)=zzq(1:nlayer,iq)
230           zqm1(1)=zqm(1,iq)
231!               print*,iq
232!               print*,zq1
233           call vl1d(nlayer,zq1,2.,zzmass,w,zqm1)
234           do l=2,nlayer
235              zzq(l,iq)=zq1(l)
236              zqm(l,iq)=zqm1(l)
237           enddo
238         enddo
239
240!        Surface condensation affects low winds
241         if (zmflux(1).lt.0) then
242            zum(1)= zzu(1) *  (w(1)/zzmass(1))
243            zvm(1)= zzv(1) *  (w(1)/zzmass(1))
244            if (w(1).gt.zzmass(1)) then ! ensure numerical stability
245               zum(1)= (zzu(1)-zum(2))*zzmass(1)/w(1) + zum(2)
246               zvm(1)= (zzv(1)-zvm(2))*zzmass(1)/w(1) + zvm(2)
247            end if
248         end if
249                   
250         ztm(nlayer+1)= zzt(nlayer) ! should not be used, but...
251         zum(nlayer+1)= zzu(nlayer)  ! should not be used, but...
252         zvm(nlayer+1)= zzv(nlayer)  ! should not be used, but...
253         zqm(nlayer+1,1:nq)= zzq(nlayer,1:nq)
254 
255!        Tendencies on T, U, V, Q
256!        """"""""""""""""""""""""
257         DO l=1,nlayer
258 
259!           Tendencies on T
260            pdtmr(ig,l) = (1/zzmass(l)) *   &
261                (zmflux(l)*(ztm(l) - zzt(l))-zmflux(l+1)*(ztm(l+1)-zzt(l)))
262                  !JL12 the last term in Newcondens has been set to zero because we are only dealing with redistribution here
263
264!           Tendencies on U
265            pdumr(ig,l)   = (1/zzmass(l)) *( zmflux(l)*(zum(l) - zzu(l)) - zmflux(l+1)*(zum(l+1) - zzu(l)) )
266
267!           Tendencies on V
268            pdvmr(ig,l)   = (1/zzmass(l)) *( zmflux(l)*(zvm(l) - zzv(l)) - zmflux(l+1)*(zvm(l+1) - zzv(l)) )
269
270         END DO
271
272!        Tendencies on Q
273         do iq=1,nq
274            DO l=1,nlayer
275               pdqmr(ig,l,iq)= (1/zzmass(l)) *   &
276                   (zmflux(l)*(zqm(l,iq)-zzq(l,iq))- zmflux(l+1)*(zqm(l+1,iq)-zzq(l,iq)) - pdmassmr(ig,l)*zzq(l,iq))
277            END DO
278         enddo
279
280      END DO  ! loop on ig
281
282CONTAINS
283
284! *****************************************************************
285      SUBROUTINE vl1d(llm,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     
298      IMPLICIT NONE
299
300!   Arguments:
301!   ----------
302      integer,intent(in) :: llm
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       END SUBROUTINE vl1d
405
406END SUBROUTINE mass_redistribution
Note: See TracBrowser for help on using the repository browser.