source: trunk/LMDZ.MARS/libf/aeronomars/conduction.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.3 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
19c   arguments:
20c   ----------
21
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)
32
33      real,intent(out) :: zdtconduc(ngrid,nlayer)
34
35c   local:
36c   ------
37
38      INTEGER i,ig,l
39      real Akk
40      real,save :: phitop
41      real m,tmean
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)
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
61c-----------------------------------------------------------------------
62c   calcul des coefficients alpha et lambda
63c-----------------------------------------------------------------------
64
65      IF (firstcall) THEN
66!        write (*,*)'conduction: coeff to compute molecular',
67!     &             ' conductivity Akk,skk'
68!        write(*,*) Akk,skk
69! NB: Akk is undefined at this stage
70        write (*,*)'conduction: coeff to compute molecular',
71     &             ' conductivity skk = ', skk
72
73! Initialize phitop
74        phitop=0.0
75       
76        firstcall = .false.
77      ENDIF ! of IF (firstcall)
78
79      do ig=1,ngrid
80
81        zt(1)=pt(ig,1)+pdt(ig,1)*ptimestep
82c        zlay(1)=-log(pplay(ig,1)/pplev(ig,1))*Rnew(ig,1)*zt(1)/g
83c        zlev(1)=0.0
84        zlay(1)=zzlay(ig,1)
85        zlev(1)=zzlev(ig,1)
86     
87        do i=2,nlayer
88
89          zt(i)=pt(ig,i)+pdt(ig,i)*ptimestep
90c          tmean=zt(i)
91c          if(zt(i).ne.zt(i-1))
92c     &    tmean=(zt(i)-zt(i-1))/log(zt(i)/zt(i-1))
93c          zlay(i)= zlay(i-1)
94c     &          -log(pplay(ig,i)/pplay(ig,i-1))*Rnew(ig,i-1)*tmean/g
95c          zlev(i)= zlev(i-1)
96c     &         -log(pplev(ig,i)/pplev(ig,i-1))*Rnew(ig,i-1)*tmean/g
97        zlay(i)=zzlay(ig,i)
98        zlev(i)=zzlev(ig,i)
99        enddo
100       
101c        zlev(nlayer+1)= zlev(nlayer)
102c     &         -log(max(pplev(ig,nlayer+1),1.e-30)/pplev(ig,nlayer))
103c     &           *Rnew(ig,nlayer)*tmean/g
104c        if(pplev(ig,nlayer+1).eq.0.)
105c     &     zlev(nlayer+1)=zlev(nlayer)+(zlay(nlayer)-zlay(nlayer-1))
106     
107        zlev(nlayer+1)= zlev(nlayer)+10000.
108
109        Akk=Akknew(ig,1)
110        lambda(1) = Akk*tsurf(ig)**skk/zlay(1)   
111
112        DO i = 2 , nlayer
113          Akk=Akknew(ig,i)
114          lambda(i)=Akk*zt(i)**skk/(zlay(i)-zlay(i-1))
115        ENDDO
116        DO i=1,nlayer-1
117          muvol(i)=pplay(ig,i)/(rnew(ig,i)*zt(i))
118          alpha(i)=cpnew(ig,i)*(muvol(i)/ptimestep)
119     $                        *(zlev(i+1)-zlev(i))
120        ENDDO
121
122        muvol(nlayer)=pplay(ig,nlayer)/(rnew(ig,nlayer)*zt(nlayer))
123        alpha(nlayer)=cpnew(ig,i)*(muvol(nlayer)/ptimestep)
124     $                       *(zlev(nlayer+1)-zlev(nlayer))
125
126c--------------------------------------------------------------------
127c
128c     calcul des coefficients C et D
129c
130c-------------------------------------------------------------------
131
132        den(1)=alpha(1)+lambda(2)+lambda(1)
133        C(1)=lambda(1)*(tsurf(ig)-zt(1))+lambda(2)*(zt(2)-zt(1))
134        C(1)=C(1)/den(1)             
135        D(1)=lambda(2)/den(1)           
136   
137        DO i = 2,nlayer-1
138          den(i)=alpha(i)+lambda(i+1)
139          den(i)=den(i)+lambda(i)*(1-D(i-1))
140           
141          C(i) =lambda(i+1)*(zt(i+1)-zt(i))
142     $         +lambda(i)*(zt(i-1)-zt(i)+C(i-1))   
143          C(i) =C(i)/den(i)           
144
145          D(i) =lambda(i+1) / den(i)
146        ENDDO
147
148        den(nlayer)=alpha(nlayer) + lambda(nlayer) * (1-D(nlayer-1))
149        C(nlayer)=C(nlayer-1)+zt(nlayer-1)-zt(nlayer)
150        C(nlayer)=(C(nlayer)*lambda(nlayer)+phitop) / den(nlayer)
151               
152c----------------------------------------------------------------------
153c
154c      calcul de la nouvelle temperature ptconduc
155c
156c----------------------------------------------------------------------
157
158        DO i=1,nlayer
159          pdtc(i)=0.
160        ENDDO
161        pdtc(nlayer)=C(nlayer)
162        DO i=nlayer-1,1,-1
163          pdtc(i)=C(i)+D(i)*pdtc(i+1)
164        ENDDO
165c-----------------------------------------------------------------------
166c
167c     calcul de la tendance zdtconduc
168c
169c-----------------------------------------------------------------------
170   
171        DO i=1,nlayer
172          zdtconduc(ig,i)=pdtc(i)/ptimestep
173        ENDDO
174
175      enddo ! of do ig=1,ngrid
176
177      RETURN
178      END
Note: See TracBrowser for help on using the repository browser.