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

Last change on this file since 3289 was 3158, checked in by csegonne, 13 months ago

MARS PCM
Cleaning of conduction.F, euvheat.F90, moldiff.F and molvis.F, some commented lines referring to a local calculation of layers/levels altitudes have been removed.

File size: 4.7 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
19c   arguments:
20c   ----------
21
[1047]22      integer,intent(in) :: ngrid ! number of atmospheric columns
23      integer,intent(in) :: nlayer ! number of atmospheric layers
24      real,intent(in) :: ptimestep
25      REAL,intent(in) :: pplay(ngrid,nlayer)
26      real,intent(in) :: pplev(ngrid,nlayer+1)
27      REAL,intent(in) :: zzlay(ngrid,nlayer)
28      real,intent(in) :: zzlev(ngrid,nlayer+1)
29      REAL,intent(in) :: pt(ngrid,nlayer)
30      real,intent(in) :: pdt(ngrid,nlayer)
31      real,intent(in) :: tsurf(ngrid)
[38]32
[1047]33      real,intent(out) :: zdtconduc(ngrid,nlayer)
[38]34
35c   local:
36c   ------
37
38      INTEGER i,ig,l
39      real Akk
40      real,save :: phitop
41      real m,tmean
[1047]42      REAL alpha(nlayer)
43      real zt(nlayer)
44      REAL lambda(nlayer)
45      real muvol(nlayer)
46      REAL C(nlayer)
47      real D(nlayer)
48      real den(nlayer)
49      REAL pdtc(nlayer)
50      real zlay(nlayer)
51      real zlev(nlayer+1)
[38]52
53c   constants used locally
54c    ---------------------
55c     The atmospheric conductivity is a function of temperature T :
56c      conductivity = Akk* T**skk
57      REAL,PARAMETER :: skk=0.69
58     
59      logical,save :: firstcall=.true.
60
[2615]61!$OMP THREADPRIVATE(phitop,firstcall)
62
[38]63c-----------------------------------------------------------------------
64c   calcul des coefficients alpha et lambda
65c-----------------------------------------------------------------------
66
67      IF (firstcall) THEN
68!        write (*,*)'conduction: coeff to compute molecular',
69!     &             ' conductivity Akk,skk'
70!        write(*,*) Akk,skk
71! NB: Akk is undefined at this stage
72        write (*,*)'conduction: coeff to compute molecular',
73     &             ' conductivity skk = ', skk
74
75! Initialize phitop
76        phitop=0.0
77       
78        firstcall = .false.
79      ENDIF ! of IF (firstcall)
80
81      do ig=1,ngrid
82
83        zt(1)=pt(ig,1)+pdt(ig,1)*ptimestep
84        zlay(1)=zzlay(ig,1)
85        zlev(1)=zzlev(ig,1)
86     
[1047]87        do i=2,nlayer
[38]88
89          zt(i)=pt(ig,i)+pdt(ig,i)*ptimestep
[3158]90          zlay(i)=zzlay(ig,i)
91          zlev(i)=zzlev(ig,i)
[38]92        enddo
[3158]93           
[1047]94        zlev(nlayer+1)= zlev(nlayer)+10000.
[38]95
96        Akk=Akknew(ig,1)
97        lambda(1) = Akk*tsurf(ig)**skk/zlay(1)   
98
[1047]99        DO i = 2 , nlayer
[38]100          Akk=Akknew(ig,i)
101          lambda(i)=Akk*zt(i)**skk/(zlay(i)-zlay(i-1))
102        ENDDO
[1047]103        DO i=1,nlayer-1
[38]104          muvol(i)=pplay(ig,i)/(rnew(ig,i)*zt(i))
105          alpha(i)=cpnew(ig,i)*(muvol(i)/ptimestep)
106     $                        *(zlev(i+1)-zlev(i))
107        ENDDO
108
[1047]109        muvol(nlayer)=pplay(ig,nlayer)/(rnew(ig,nlayer)*zt(nlayer))
110        alpha(nlayer)=cpnew(ig,i)*(muvol(nlayer)/ptimestep)
111     $                       *(zlev(nlayer+1)-zlev(nlayer))
[38]112
113c--------------------------------------------------------------------
114c
115c     calcul des coefficients C et D
116c
117c-------------------------------------------------------------------
118
119        den(1)=alpha(1)+lambda(2)+lambda(1)
120        C(1)=lambda(1)*(tsurf(ig)-zt(1))+lambda(2)*(zt(2)-zt(1))
121        C(1)=C(1)/den(1)             
122        D(1)=lambda(2)/den(1)           
123   
[1047]124        DO i = 2,nlayer-1
[38]125          den(i)=alpha(i)+lambda(i+1)
126          den(i)=den(i)+lambda(i)*(1-D(i-1))
127           
128          C(i) =lambda(i+1)*(zt(i+1)-zt(i))
129     $         +lambda(i)*(zt(i-1)-zt(i)+C(i-1))   
130          C(i) =C(i)/den(i)           
131
132          D(i) =lambda(i+1) / den(i)
133        ENDDO
134
[1047]135        den(nlayer)=alpha(nlayer) + lambda(nlayer) * (1-D(nlayer-1))
136        C(nlayer)=C(nlayer-1)+zt(nlayer-1)-zt(nlayer)
137        C(nlayer)=(C(nlayer)*lambda(nlayer)+phitop) / den(nlayer)
[38]138               
139c----------------------------------------------------------------------
140c
141c      calcul de la nouvelle temperature ptconduc
142c
143c----------------------------------------------------------------------
144
[1047]145        DO i=1,nlayer
[38]146          pdtc(i)=0.
147        ENDDO
[1047]148        pdtc(nlayer)=C(nlayer)
149        DO i=nlayer-1,1,-1
[38]150          pdtc(i)=C(i)+D(i)*pdtc(i+1)
151        ENDDO
152c-----------------------------------------------------------------------
153c
154c     calcul de la tendance zdtconduc
155c
156c-----------------------------------------------------------------------
157   
[1047]158        DO i=1,nlayer
[38]159          zdtconduc(ig,i)=pdtc(i)/ptimestep
160        ENDDO
161
162      enddo ! of do ig=1,ngrid
163
164      RETURN
165      END
Note: See TracBrowser for help on using the repository browser.