source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/vlz_fi.F @ 224

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

Creating temporary dynamico/lmdz/saturn branche

YM

File size: 5.5 KB
Line 
1      SUBROUTINE vlz_fi(ngrid,q,pente_max,masse,w,wq)
2c
3c     Auteurs:   P.Le Van, F.Hourdin, F.Forget 
4c
5c    ********************************************************************
6c     Shema  d'advection " pseudo amont " dans la verticale
7c    pour appel dans la physique (sedimentation)
8c    ********************************************************************
9c    q rapport de melange (kg/kg)...
10c    masse : masse de la couche Dp/g
11c    w : masse d'atm ``transferee'' a chaque pas de temps (kg.m-2)
12c    pente_max = 2 conseillee
13c
14c
15c   --------------------------------------------------------------------
16      IMPLICIT NONE
17c
18#include "dimensions.h"
19#include "dimphys.h"
20
21c
22c
23c   Arguments:
24c   ----------
25      integer ngrid
26      real masse(ngrid,llm),pente_max
27      REAL q(ngrid,llm)
28      REAL w(ngrid,llm)
29      REAL wq(ngrid,llm+1)
30c
31c      Local 
32c   ---------
33c
34      INTEGER i,ij,l,j,ii
35c
36
37      real dzq(ngrid,llm),dzqw(ngrid,llm),adzqw(ngrid,llm),dzqmax
38      real newmasse
39      real sigw, Mtot, MQtot
40      integer m
41
42      REAL      SSUM,CVMGP,CVMGT
43      integer ismax,ismin
44
45
46c    On oriente tout dans le sens de la pression c'est a dire dans le
47c    sens de W
48
49      do l=2,llm
50         do ij=1,ngrid
51            dzqw(ij,l)=q(ij,l-1)-q(ij,l)
52            adzqw(ij,l)=abs(dzqw(ij,l))
53         enddo
54      enddo
55
56      do l=2,llm-1
57         do ij=1,ngrid
58#ifdef CRAY
59            dzq(ij,l)=0.5*
60     ,      cvmgp(dzqw(ij,l)+dzqw(ij,l+1),0.,dzqw(ij,l)*dzqw(ij,l+1))
61#else
62            if(dzqw(ij,l)*dzqw(ij,l+1).gt.0.) then
63                dzq(ij,l)=0.5*(dzqw(ij,l)+dzqw(ij,l+1))
64            else
65                dzq(ij,l)=0.
66            endif
67#endif
68            dzqmax=pente_max*min(adzqw(ij,l),adzqw(ij,l+1))
69            dzq(ij,l)=sign(min(abs(dzq(ij,l)),dzqmax),dzq(ij,l))
70         enddo
71      enddo
72
73      do ij=1,ngrid
74         dzq(ij,1)=0.
75         dzq(ij,llm)=0.
76      enddo
77c ---------------------------------------------------------------
78c   .... calcul des termes d'advection verticale  .......
79c ---------------------------------------------------------------
80
81c calcul de  - d( q   * w )/ d(sigma)    qu'on ajoute a  dq pour calculer dq
82c
83c      No flux at the model top:
84       do ij=1,ngrid
85          wq(ij,llm+1)=0.
86       enddo
87
88c      1) Compute wq where w > 0 (down) (ALWAYS FOR SEDIMENTATION)     
89c      ===============================
90
91       do l = 1,llm          ! loop different than when w<0
92        do ij=1,ngrid
93
94         if(w(ij,l).gt.0.)then
95
96c         Regular scheme (transfered mass < 1 layer)
97c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
98          if(w(ij,l).le.masse(ij,l))then
99            sigw=w(ij,l)/masse(ij,l)
100            wq(ij,l)=w(ij,l)*(q(ij,l)+0.5*(1.-sigw)*dzq(ij,l))
101           
102
103c         Extended scheme (transfered mass > 1 layer)
104c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
105          else
106            m=l
107            Mtot = masse(ij,m)
108            MQtot = masse(ij,m)*q(ij,m)
109            if(m.ge.llm)goto 88
110            do while(w(ij,l).gt.(Mtot+masse(ij,m+1)))
111                m=m+1
112                Mtot = Mtot + masse(ij,m)
113                MQtot = MQtot + masse(ij,m)*q(ij,m)
114                if(m.ge.llm)goto 88
115            end do
116 88         continue
117            if (m.lt.llm) then
118                sigw=(w(ij,l)-Mtot)/masse(ij,m+1)
119                wq(ij,l)=(MQtot + (w(ij,l)-Mtot)*
120     &          (q(ij,m+1)+0.5*(1.-sigw)*dzq(ij,m+1)) )
121            else
122                w(ij,l) = Mtot
123                wq(ij,l) = Mqtot
124            end if
125          end if
126         end if
127        enddo
128       enddo
129
130c      2) Compute wq where w < 0 (up) (NOT USEFUL FOR SEDIMENTATION)     
131c      ===============================
132       goto 99 ! SKIPPING THIS PART FOR SEDIMENTATION
133
134c      Surface flux up:
135       do ij=1,ngrid
136         if(w(ij,1).lt.0.) wq(ij,1)=0. ! warning : not always valid
137       end do
138
139       do l = 1,llm-1  ! loop different than when w>0
140        do ij=1,ngrid
141         if(w(ij,l+1).le.0)then
142
143c         Regular scheme (transfered mass < 1 layer)
144c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
145          if(-w(ij,l+1).le.masse(ij,l))then
146            sigw=w(ij,l+1)/masse(ij,l)
147            wq(ij,l+1)=w(ij,l+1)*(q(ij,l)-0.5*(1.+sigw)*dzq(ij,l))
148c         Extended scheme (transfered mass > 1 layer)
149c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
150          else
151             m = l-1
152             Mtot = masse(ij,m+1)
153             MQtot = masse(ij,m+1)*q(ij,m+1)
154             if (m.le.0)goto 77
155             do while(-w(ij,l+1).gt.(Mtot+masse(ij,m)))
156                m=m-1
157                Mtot = Mtot + masse(ij,m+1)
158                MQtot = MQtot + masse(ij,m+1)*q(ij,m+1)
159                if (m.le.0)goto 77
160             end do
161 77          continue
162
163             if (m.gt.0) then
164                sigw=(w(ij,l+1)+Mtot)/masse(ij,m)
165                wq(ij,l+1)= (MQtot + (-w(ij,l+1)-Mtot)*
166     &          (q(ij,m)-0.5*(1.+sigw)*dzq(ij,m))  )
167             else
168c               wq(ij,l+1)= (MQtot + (-w(ij,l+1)-Mtot)*qm(ij,1))
169                write(*,*) 'a rather weird situation in vlz_fi !'
170                stop
171             end if
172          endif
173         endif
174        enddo
175       enddo
176 99    continue
177
178      do l=1,llm
179         do ij=1,ngrid
180
181cccccccc lines below not used for sedimentation (No real flux)
182ccccc       newmasse=masse(ij,l)+w(ij,l+1)-w(ij,l) 
183ccccc       q(ij,l)=(q(ij,l)*masse(ij,l)+wq(ij,l+1)-wq(ij,l))
184ccccc&         /newmasse
185ccccc       masse(ij,l)=newmasse
186
187            q(ij,l)=q(ij,l) +  (wq(ij,l+1)-wq(ij,l))/masse(ij,l)
188
189         enddo
190      enddo
191
192
193
194      return
195      end
Note: See TracBrowser for help on using the repository browser.