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

Last change on this file since 2599 was 1266, checked in by aslmd, 11 years ago

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

  • Optimized computations in paramfoto_compact (twice less dlog10 calculations)
  • Checked consistency before/after modification in debug mode
  • Checked performance is not impacted (same as before)
File size: 5.5 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
22c   arguments:
23c   ----------
24
25      integer,intent(in) :: ngrid ! number of atmospheric columns
26      integer,intent(in) :: nlayer ! number of atmospheric layers
27      REAL ptimestep
28      REAL pplay(ngrid,nlayer)
29      REAL pplev(ngrid,nlayer+1)
30      REAL zzlay(ngrid,nlayer)
31      REAL zzlev(ngrid,nlayer+1)
32      real pt(ngrid,nlayer)
33      real tsurf(ngrid)
34      REAL pvel(ngrid,nlayer)
35      REAL pdvel(ngrid,nlayer)
36      real pdteuv(ngrid,nlayer)
37      real pdtconduc(ngrid,nlayer)
38
39      real zdvelmolvis(ngrid,nlayer)
40
41c   local:
42c   ------
43
44      INTEGER l,ig, nz
45      real Akk,phitop,fac, m, tmean
46      REAL zvel(nlayer)
47      real zt(nlayer)
48      REAL alpha(nlayer)
49      REAL lambda(nlayer)
50      real muvol(nlayer)
51      REAL C(nlayer)
52      real D(nlayer)
53      real den(nlayer)
54      REAL pdvelm(nlayer)
55      REAL zlay(nlayer)
56      real zlev(nlayer+1)
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=nlayer
90
91      do ig=1,ngrid
92
93        zt(1)=pt(ig,1)+(pdteuv(ig,1)+pdtconduc(ig,1))*ptimestep
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)+(pdteuv(ig,l)+pdtconduc(ig,l))*ptimestep
103          zvel(l)=pvel(ig,l)
104c          tmean=zt(l)
105c          if(zt(l).ne.zt(l-1)) tmean=(zt(l)-zt(l-1))/log(zt(l)/zt(l-1))
106c          zlay(l)= zlay(l-1)
107c     &          -log(pplay(ig,l)/pplay(ig,l-1))*Rnew(ig,l-1)*tmean/g
108c          zlev(l)= zlev(l-1)
109c     &         -log(pplev(ig,l)/pplev(ig,l-1))*Rnew(ig,l-1)*tmean/g
110        zlay(l)=zzlay(ig,l)
111        zlev(l)=zzlev(ig,l)
112        enddo
113
114c          zlev(nz+1)= zlev(nz)
115c     &         -log(max(pplev(ig,nz+1),1.e-30)/pplev(ig,nz))
116c     &          *Rnew(ig,nz)*tmean/g
117c          if(pplev(ig,nz+1).eq.0.)
118c     &       zlev(nz+1)=zlev(nz)+(zlay(nz)-zlay(nz-1))
119
120          zlev(nz+1)= zlev(nz)+10000.
121
122        fac=0.25*(9.*cpnew(ig,1)-5.*(cpnew(ig,1)-rnew(ig,1)))
123        Akk=Akknew(ig,1)
124        lambda(1)=Akk*tsurf(ig)**skk/zlay(1)/fac   
125c        write(*,*) 'rnew(ig,nz)  ',ig , rnew(ig,nz)
126
127        DO l=2,nz
128          fac=(9.*cpnew(ig,l)-5.*(cpnew(ig,l)-rnew(ig,l)))/4.
129          Akk=Akknew(ig,l)
130          lambda(l)=Akk/fac*zt(l)**skk/(zlay(l)-zlay(l-1))
131        ENDDO
132   
133        DO l=1,nz-1
134          muvol(l)=pplay(ig,l)/(rnew(ig,l)*zt(l))
135          alpha(l)=(muvol(l)/ptimestep)*(zlev(l+1)-zlev(l))
136        ENDDO
137        muvol(nz)=pplay(ig,nz)/(rnew(ig,nz)*zt(nz))
138        alpha(nz)=(muvol(nz)/ptimestep)*(zlev(nz+1)-zlev(nz))
139
140c--------------------------------------------------------------------
141c
142c     calcul des coefficients C et D
143c
144c-------------------------------------------------------------------
145
146      den(1)=alpha(1)+lambda(2)+lambda(1)
147      C(1)=lambda(1)*(velsurf-zvel(1))+lambda(2)*(zvel(2)-zvel(1))
148      C(1)=C(1)/den(1)       
149      D(1)=lambda(2)/den(1)           
150   
151      DO l = 2,nz-1
152         den(l)=alpha(l)+lambda(l+1)
153         den(l)=den(l)+lambda(l)*(1-D(l-1))
154         
155         C(l) =lambda(l+1)*(zvel(l+1)-zvel(l))
156     $        +lambda(l)*(zvel(l-1)-zvel(l)+C(l-1))   
157         C(l) =C(l)/den(l)           
158
159         D(l) =lambda(l+1) / den(l)
160      ENDDO
161
162      den(nz)=alpha(nz) + lambda(nz) * (1-D(nz-1))
163      C(nz)=C(nz-1)+zvel(nz-1)-zvel(nz)
164      C(nz)=(C(nz)*lambda(nz)+phitop) / den(nz)
165               
166c----------------------------------------------------------------------
167c
168c      calcul de la nouvelle pdvelm
169c
170c----------------------------------------------------------------------
171
172      DO l=1,nz
173         pdvelm(l)=0.
174      ENDDO
175         pdvelm(nz)=C(nz)
176      DO l=nz-1,1,-1
177         pdvelm(l)=C(l)+D(l)*pdvelm(l+1)
178      ENDDO
179c-----------------------------------------------------------------------
180c
181c     calcul de la tendance zdvelmolvis
182c
183c-----------------------------------------------------------------------
184   
185      DO l=1,nz
186        zdvelmolvis(ig,l)=pdvelm(l)/ptimestep
187      ENDDO
188
189      ENDDO             ! boucle sur ngrid
190
191      RETURN
192      END
Note: See TracBrowser for help on using the repository browser.