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

Last change on this file since 313 was 313, checked in by ymipsl, 10 years ago
  • implement splitting of XIOS file for lmdz physics
  • Termination is done properly in parallel by calling MPI_ABORT instead of abort or stop

YM

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