source: trunk/WRF.COMMON/WRFV2/mars_lmd/libf/aeronomars/conduction.F @ 3026

Last change on this file since 3026 was 11, checked in by aslmd, 14 years ago

spiga@svn-planeto:ajoute le modele meso-echelle martien

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