source: trunk/LMDZ.MARS/libf/phymars/vlz_fi.F @ 1242

Last change on this file since 1242 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 5.6 KB
Line 
1      SUBROUTINE vlz_fi(ngrid,nlay,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 ! number of atmospheric columns
26      integer,intent(in) :: nlay ! number of atmospheric layers
27      real masse(ngrid,nlay),pente_max
28      REAL q(ngrid,nlay)
29      REAL w(ngrid,nlay)
30      REAL wq(ngrid,nlay+1)
31c
32c      Local
33c   ---------
34c
35      INTEGER i,ij,l,j,ii
36c
37
38      real dzq(ngrid,nlay),dzqw(ngrid,nlay),adzqw(ngrid,nlay),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,nlay
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,nlay-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,nlay)=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,nlay+1)=0.
87       enddo
88
89c      1) Compute wq where w > 0 (down) (ALWAYS FOR SEDIMENTATION)     
90c      ===============================
91
92       do l = 1,nlay          ! 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.nlay)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.nlay)goto 88
116            end do
117 88         continue
118            if (m.lt.nlay) 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,nlay-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,nlay
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
195      return
196      end
Note: See TracBrowser for help on using the repository browser.