source: trunk/LMDZ.MARS/libf/aeronomars/molvis.F @ 1119

Last change on this file since 1119 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.7 KB
Line 
1       SUBROUTINE molvis(ngrid,nlayer,ptimestep,
2     &            pplay,pplev,pt,pdteuv,pdtconduc
3     $           ,pvel,tsurf,zzlev,zzlay,zdvelmolvis)
4     
5      use conc_mod, only: cpnew, Akknew, rnew
6      IMPLICIT NONE
7
8c=======================================================================
9c
10c   Molecular Viscosity Diffusion
11
12c   Based on conduction.F  by N. Descamp, F. Forget 05/1999
13c
14c   modified by M. Angelats i Coll
15c
16c=======================================================================
17
18c-----------------------------------------------------------------------
19c   declarations:
20c-----------------------------------------------------------------------
21
22!#include "dimensions.h"
23!#include "dimphys.h"
24!#include "comcstfi.h"
25!#include "surfdat.h"
26!#include "chimiedata.h"
27!#include "conc.h"
28
29c   arguments:
30c   ----------
31
32      integer,intent(in) :: ngrid ! number of atmospheric columns
33      integer,intent(in) :: nlayer ! number of atmospheric layers
34      REAL ptimestep
35      REAL pplay(ngrid,nlayer)
36      REAL pplev(ngrid,nlayer+1)
37      REAL zzlay(ngrid,nlayer)
38      REAL zzlev(ngrid,nlayer+1)
39      real pt(ngrid,nlayer)
40      real tsurf(ngrid)
41      REAL pvel(ngrid,nlayer)
42      REAL pdvel(ngrid,nlayer)
43      real pdteuv(ngrid,nlayer)
44      real pdtconduc(ngrid,nlayer)
45
46      real zdvelmolvis(ngrid,nlayer)
47
48c   local:
49c   ------
50
51      INTEGER l,ig, nz
52      real Akk,phitop,fac, m, tmean
53      REAL zvel(nlayer)
54      real zt(nlayer)
55      REAL alpha(nlayer)
56      REAL lambda(nlayer)
57      real muvol(nlayer)
58      REAL C(nlayer)
59      real D(nlayer)
60      real den(nlayer)
61      REAL pdvelm(nlayer)
62      REAL zlay(nlayer)
63      real zlev(nlayer+1)
64
65c   constants used locally
66c    ---------------------
67c     The atmospheric conductivity is a function of temperature T :
68c      conductivity = Akk* T**skk
69c     Molecular viscosity is related to thermal conductivity by:
70c       conduc = 0.25*(9*gamma - 5)* Cv * molvis
71c     where gamma = Cp/Cv.  For dry air.
72
73
74      REAL,PARAMETER :: skk=0.69
75
76      REAL,PARAMETER :: velsurf =0.0
77     
78      logical,save :: firstcall=.true.
79
80c-----------------------------------------------------------------------
81c   calcul des coefficients alpha et lambda
82c-----------------------------------------------------------------------
83
84      IF (firstcall) THEN
85!        write(*,*)'molvis: coeff of molecular viscosity Akk,skk,factor'
86!        write(*,*) Akk,skk,fac
87! NB: Akk and fac are undefined at firstcall
88        write(*,*)'molvis: coeff of molecular viscosity skk ', skk
89       
90        firstcall = .false.
91      END IF
92
93! Initialize phitop
94      phitop=0.0
95
96      nz=nlayer
97
98      do ig=1,ngrid
99
100        zt(1)=pt(ig,1)+(pdteuv(ig,1)+pdtconduc(ig,1))*ptimestep
101        zvel(1)=pvel(ig,1)
102c        zlay(1)=-log(pplay(ig,1)/pplev(ig,1))*Rnew(ig,1)*zt(1)/g
103c        zlev(1)=0.0
104
105        zlay(1)=zzlay(ig,1)
106        zlev(1)=zzlev(ig,1)
107
108        do l=2,nz
109          zt(l)=pt(ig,l)+(pdteuv(ig,l)+pdtconduc(ig,l))*ptimestep
110          zvel(l)=pvel(ig,l)
111c          tmean=zt(l)
112c          if(zt(l).ne.zt(l-1)) tmean=(zt(l)-zt(l-1))/log(zt(l)/zt(l-1))
113c          zlay(l)= zlay(l-1)
114c     &          -log(pplay(ig,l)/pplay(ig,l-1))*Rnew(ig,l-1)*tmean/g
115c          zlev(l)= zlev(l-1)
116c     &         -log(pplev(ig,l)/pplev(ig,l-1))*Rnew(ig,l-1)*tmean/g
117        zlay(l)=zzlay(ig,l)
118        zlev(l)=zzlev(ig,l)
119        enddo
120
121c          zlev(nz+1)= zlev(nz)
122c     &         -log(max(pplev(ig,nz+1),1.e-30)/pplev(ig,nz))
123c     &          *Rnew(ig,nz)*tmean/g
124c          if(pplev(ig,nz+1).eq.0.)
125c     &       zlev(nz+1)=zlev(nz)+(zlay(nz)-zlay(nz-1))
126
127          zlev(nz+1)= zlev(nz)+10000.
128
129        fac=0.25*(9.*cpnew(ig,1)-5.*(cpnew(ig,1)-rnew(ig,1)))
130        Akk=Akknew(ig,1)
131        lambda(1)=Akk*tsurf(ig)**skk/zlay(1)/fac   
132c        write(*,*) 'rnew(ig,nz)  ',ig , rnew(ig,nz)
133
134        DO l=2,nz
135          fac=(9.*cpnew(ig,l)-5.*(cpnew(ig,l)-rnew(ig,l)))/4.
136          Akk=Akknew(ig,l)
137          lambda(l)=Akk/fac*zt(l)**skk/(zlay(l)-zlay(l-1))
138        ENDDO
139   
140        DO l=1,nz-1
141          muvol(l)=pplay(ig,l)/(rnew(ig,l)*zt(l))
142          alpha(l)=(muvol(l)/ptimestep)*(zlev(l+1)-zlev(l))
143        ENDDO
144        muvol(nz)=pplay(ig,nz)/(rnew(ig,nz)*zt(nz))
145        alpha(nz)=(muvol(nz)/ptimestep)*(zlev(nz+1)-zlev(nz))
146
147c--------------------------------------------------------------------
148c
149c     calcul des coefficients C et D
150c
151c-------------------------------------------------------------------
152
153      den(1)=alpha(1)+lambda(2)+lambda(1)
154      C(1)=lambda(1)*(velsurf-zvel(1))+lambda(2)*(zvel(2)-zvel(1))
155      C(1)=C(1)/den(1)       
156      D(1)=lambda(2)/den(1)           
157   
158      DO l = 2,nz-1
159         den(l)=alpha(l)+lambda(l+1)
160         den(l)=den(l)+lambda(l)*(1-D(l-1))
161         
162         C(l) =lambda(l+1)*(zvel(l+1)-zvel(l))
163     $        +lambda(l)*(zvel(l-1)-zvel(l)+C(l-1))   
164         C(l) =C(l)/den(l)           
165
166         D(l) =lambda(l+1) / den(l)
167      ENDDO
168
169      den(nz)=alpha(nz) + lambda(nz) * (1-D(nz-1))
170      C(nz)=C(nz-1)+zvel(nz-1)-zvel(nz)
171      C(nz)=(C(nz)*lambda(nz)+phitop) / den(nz)
172               
173c----------------------------------------------------------------------
174c
175c      calcul de la nouvelle pdvelm
176c
177c----------------------------------------------------------------------
178
179      DO l=1,nz
180         pdvelm(l)=0.
181      ENDDO
182         pdvelm(nz)=C(nz)
183      DO l=nz-1,1,-1
184         pdvelm(l)=C(l)+D(l)*pdvelm(l+1)
185      ENDDO
186c-----------------------------------------------------------------------
187c
188c     calcul de la tendance zdvelmolvis
189c
190c-----------------------------------------------------------------------
191   
192      DO l=1,nz
193        zdvelmolvis(ig,l)=pdvelm(l)/ptimestep
194      ENDDO
195
196      ENDDO             ! boucle sur ngrid
197
198      RETURN
199      END
Note: See TracBrowser for help on using the repository browser.