source: trunk/LMDZ.VENUS/libf/phyvenus/molvis.F @ 2187

Last change on this file since 2187 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

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