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

Last change on this file since 134 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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