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

Last change on this file since 227 was 227, checked in by milmd, 10 years ago

Last LMDZ version (1315) with OpenMP directives and other stuff

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