source: trunk/LMDZ.VENUS/libf/phyvenus/soil.F @ 3461

Last change on this file since 3461 was 2539, checked in by emillour, 3 years ago

Venus GCM:
Fix soil model so that it correctly computes soil temperatures at the first time step. And in the process make it 1+1=2 compliant.
VB+EM

File size: 7.1 KB
Line 
1!
2! $Header: /home/cvsroot/LMDZ4/libf/phylmd/soil.F,v 1.1.1.1 2004/05/19 12:53:09 lmdzadmin Exp $
3!
4      SUBROUTINE soil(ptimestep, knon, ptsrf, ptsoil,
5     s          pcapcal, pfluxgrd)
6
7c=======================================================================
8c
9c   Auteur:  Frederic Hourdin     30/01/92
10c   -------
11c
12c   objet:  computation of : the soil temperature evolution
13c   ------                   the surfacic heat capacity "Capcal"
14c                            the surface conduction flux pcapcal
15c
16c
17c   Method: implicit time integration
18c   -------
19c   Consecutive ground temperatures are related by:
20c           T(k+1) = C(k) + D(k)*T(k)  (1)
21c   the coefficients C and D are computed at the t-dt time-step.
22c   Routine structure:
23c   1)new temperatures are computed  using (1)
24c   2)C and D coefficients are computed from the new temperature
25c     profile for the t+dt time-step
26c   3)the coefficients A and B are computed where the diffusive
27c     fluxes at the t+dt time-step is given by
28c            Fdiff = A + B Ts(t+dt)
29c     or     Fdiff = F0 + Capcal (Ts(t+dt)-Ts(t))/dt
30c            with F0 = A + B (Ts(t))
31c                 Capcal = B*dt
32c           
33c   Interface:
34c   ----------
35c
36c   Arguments:
37c   ----------
38c   ptimestep            physical timestep (s)
39c   ptsrf(klon)          surface temperature at time-step t (K)
40c   ptsoil(klon,nsoilmx) temperature inside the ground (K)
41c   pcapcal(klon)        surfacic specific heat (W*m-2*s*K-1)
42c   pfluxgrd(klon)       surface diffusive flux from ground (Wm-2)
43c   
44c=======================================================================
45c   declarations:
46c   -------------
47
48      use dimphy, only: klon
49      IMPLICIT NONE
50      include "YOMCST.h"
51      include "dimsoil.h"
52      include "clesphys.h"
53
54c-----------------------------------------------------------------------
55c  arguments
56c  ---------
57
58      REAL, intent(IN) :: ptimestep
59      INTEGER, intent(IN) :: knon
60      REAL, intent(IN) :: ptsrf(klon)
61      REAL, intent(OUT) :: ptsoil(klon,nsoilmx)
62      REAL, intent(OUT) :: pcapcal(klon),pfluxgrd(klon)
63
64c-----------------------------------------------------------------------
65c  local arrays
66c  ------------
67
68      INTEGER ig,jk
69      REAL zdz2(nsoilmx),z1(klon)
70      REAL min_period,dalph_soil
71      REAL ztherm_i(klon)
72
73c   local saved variables:
74c   ----------------------
75      REAL,SAVE :: dz1(nsoilmx),dz2(nsoilmx)
76      REAL,allocatable,save :: zc(:,:),zd(:,:)
77      REAL,SAVE :: lambda
78      LOGICAL,SAVE :: firstcall=.true.
79
80c-----------------------------------------------------------------------
81c   Depths:
82c   -------
83
84      REAL fz,rk,fz1,rk1,rk2
85      fz(rk)=fz1*(dalph_soil**rk-1.)/(dalph_soil-1.)
86
87      pfluxgrd(:) = 0.
88 
89      ! on Venus thermal inertia is assumed constant over the globe
90      DO ig = 1, knon
91          ztherm_i(ig)   = inertie
92      ENDDO
93
94      IF (firstcall) THEN
95
96         allocate(zc(klon,nsoilmx),zd(klon,nsoilmx))
97
98c-----------------------------------------------------------------------
99c   ground levels
100c   grnd=z/l where l is the skin depth of the diurnal cycle:
101c   --------------------------------------------------------
102
103c VENUS : A REVOIR !!!!
104         min_period=20000. ! in seconds
105         dalph_soil=2.    ! ratio between successive layer sizes
106
107         OPEN(99,file='soil.def',status='old',form='formatted',err=9999)
108         READ(99,*) min_period
109         READ(99,*) dalph_soil
110         PRINT*,'Discretization for the soil model'
111         PRINT*,'First level e-folding depth',min_period,
112     s   '   dalph',dalph_soil
113         CLOSE(99)
1149999     CONTINUE
115
116c   The first soil layer depth, based on min_period
117         fz1=sqrt(min_period/3.14)
118
119         DO jk=1,nsoilmx
120            rk1=jk
121            rk2=jk-1
122            dz2(jk)=fz(rk1)-fz(rk2)
123         ENDDO
124         DO jk=1,nsoilmx-1
125            rk1=jk+.5
126            rk2=jk-.5
127            dz1(jk)=1./(fz(rk1)-fz(rk2))
128         ENDDO
129         lambda=fz(.5)*dz1(1)
130         PRINT*,'full layers, intermediate layers (seconds)'
131         DO jk=1,nsoilmx
132            rk=jk
133            rk1=jk+.5
134            rk2=jk-.5
135            PRINT *,'fz=',
136     .               fz(rk1)*fz(rk2)*3.14,fz(rk)*fz(rk)*3.14
137         ENDDO
138         
139c-----------------------------------------------------------------------
140c   Computation of the Cgrd and Dgrd coefficient for the next step:
141c   ---------------------------------------------------------------
142         DO jk=1,nsoilmx
143            zdz2(jk)=dz2(jk)/ptimestep
144         ENDDO
145
146         DO ig=1,knon
147            z1(ig)=zdz2(nsoilmx)+dz1(nsoilmx-1)
148            zc(ig,nsoilmx-1)=
149     $          zdz2(nsoilmx)*ptsoil(ig,nsoilmx)/z1(ig)
150            zd(ig,nsoilmx-1)=dz1(nsoilmx-1)/z1(ig)
151         ENDDO
152
153         DO jk=nsoilmx-1,2,-1
154            DO ig=1,knon
155               z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)
156     $            *(1.-zd(ig,jk)))
157               zc(ig,jk-1)=
158     s         (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))
159     $             *z1(ig)
160               zd(ig,jk-1)=dz1(jk-1)*z1(ig)
161            ENDDO
162         ENDDO
163         firstcall =.false.
164
165      ENDIF !--not firstcall
166
167c-----------------------------------------------------------------------
168c   Computation of the soil temperatures using the Cgrd and Dgrd
169c  coefficient computed at the previous time-step:
170c  -----------------------------------------------
171
172c        temperature in the first soil layer
173         DO ig=1,knon
174            ptsoil(ig,1)=(lambda*zc(ig,1)+ptsrf(ig))/
175     s      (lambda*(1.-zd(ig,1))+1.)
176         ENDDO
177
178c        temperatures in the other soil layers
179         DO jk=1,nsoilmx-1
180            DO ig=1,knon
181               ptsoil(ig,jk+1)=zc(ig,jk)+zd(ig,jk)*ptsoil(ig,jk)
182            ENDDO
183         ENDDO
184
185c-----------------------------------------------------------------------
186c   Computation of the Cgrd and Dgrd coefficient for the next step:
187c   ---------------------------------------------------------------
188
189      DO jk=1,nsoilmx
190         zdz2(jk)=dz2(jk)/ptimestep
191      ENDDO
192
193      DO ig=1,knon
194         z1(ig)=zdz2(nsoilmx)+dz1(nsoilmx-1)
195         zc(ig,nsoilmx-1)=
196     $       zdz2(nsoilmx)*ptsoil(ig,nsoilmx)/z1(ig)
197         zd(ig,nsoilmx-1)=dz1(nsoilmx-1)/z1(ig)
198      ENDDO
199
200      DO jk=nsoilmx-1,2,-1
201         DO ig=1,knon
202            z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)
203     $         *(1.-zd(ig,jk)))
204            zc(ig,jk-1)=
205     s      (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))
206     $          *z1(ig)
207            zd(ig,jk-1)=dz1(jk-1)*z1(ig)
208         ENDDO
209      ENDDO
210
211c-----------------------------------------------------------------------
212c   computation of the surface diffusive flux from ground and
213c   calorific capacity of the ground:
214c   ---------------------------------
215
216      DO ig=1,knon
217         pfluxgrd(ig)=ztherm_i(ig)*dz1(1)*
218     s   (zc(ig,1)+(zd(ig,1)-1.)*ptsoil(ig,1))
219         pcapcal(ig)=ztherm_i(ig)*
220     s   (dz2(1)+ptimestep*(1.-zd(ig,1))*dz1(1))
221         z1(ig)=lambda*(1.-zd(ig,1))+1.
222         pcapcal(ig)=pcapcal(ig)/z1(ig)
223         pfluxgrd(ig) = pfluxgrd(ig)
224     s   + pcapcal(ig) * (ptsoil(ig,1) * z1(ig)
225     $       - lambda * zc(ig,1)
226     $       - ptsrf(ig))
227     s   /ptimestep
228      ENDDO
229
230     
231      END
Note: See TracBrowser for help on using the repository browser.