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

Last change on this file since 1127 was 1047, checked in by emillour, 12 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

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