source: trunk/LMDZ.MARS/libf/aeronomars/conduction.F @ 1233

Last change on this file since 1233 was 1226, checked in by aslmd, 11 years ago

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

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