source: trunk/libf/phyvenus/soil.F @ 24

Last change on this file since 24 was 3, checked in by slebonnois, 14 years ago

Creation de repertoires:

  • chantiers : pour communiquer sur nos projets de modifs
  • documentation : pour stocker les docs

Ajout de:

  • libf/phytitan : physique de Titan
  • libf/chimtitan: chimie de Titan
  • libf/phyvenus : physique de Venus
File size: 6.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      IMPLICIT NONE
7
8c=======================================================================
9c
10c   Auteur:  Frederic Hourdin     30/01/92
11c   -------
12c
13c   objet:  computation of : the soil temperature evolution
14c   ------                   the surfacic heat capacity "Capcal"
15c                            the surface conduction flux pcapcal
16c
17c
18c   Method: implicit time integration
19c   -------
20c   Consecutive ground temperatures are related by:
21c           T(k+1) = C(k) + D(k)*T(k)  (1)
22c   the coefficients C and D are computed at the t-dt time-step.
23c   Routine structure:
24c   1)new temperatures are computed  using (1)
25c   2)C and D coefficients are computed from the new temperature
26c     profile for the t+dt time-step
27c   3)the coefficients A and B are computed where the diffusive
28c     fluxes at the t+dt time-step is given by
29c            Fdiff = A + B Ts(t+dt)
30c     or     Fdiff = F0 + Capcal (Ts(t+dt)-Ts(t))/dt
31c            with F0 = A + B (Ts(t))
32c                 Capcal = B*dt
33c           
34c   Interface:
35c   ----------
36c
37c   Arguments:
38c   ----------
39c   ptimestep            physical timestep (s)
40c   ptsrf(klon)          surface temperature at time-step t (K)
41c   ptsoil(klon,nsoilmx) temperature inside the ground (K)
42c   pcapcal(klon)        surfacic specific heat (W*m-2*s*K-1)
43c   pfluxgrd(klon)       surface diffusive flux from ground (Wm-2)
44c   
45c=======================================================================
46c   declarations:
47c   -------------
48
49#include "dimensions.h"
50#include "YOMCST.h"
51#include "dimphy.h"
52#include "dimsoil.h"
53#include "clesphys.h"
54
55c-----------------------------------------------------------------------
56c  arguments
57c  ---------
58
59      REAL ptimestep
60      INTEGER knon
61      REAL ptsrf(klon),ptsoil(klon,nsoilmx)
62      REAL 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 dz1(nsoilmx),dz2(nsoilmx)
76      REAL zc(klon,nsoilmx),zd(klon,nsoilmx)
77      REAL lambda
78      SAVE dz1,dz2,zc,zd,lambda
79      LOGICAL firstcall
80      SAVE firstcall
81
82      DATA firstcall/.true./
83
84c-----------------------------------------------------------------------
85c   Depthts:
86c   --------
87
88      REAL fz,rk,fz1,rk1,rk2
89      fz(rk)=fz1*(dalph_soil**rk-1.)/(dalph_soil-1.)
90      pfluxgrd(:) = 0.
91 
92      DO ig = 1, knon
93          ztherm_i(ig)   = inertie
94      ENDDO
95
96      IF (firstcall) THEN
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. ! en secondes
105         dalph_soil=2.    ! rapport entre les epaisseurs de 2 couches succ.
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   la premiere couche represente un dixieme de cycle diurne
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         firstcall =.false.
139
140      ELSE   !--not firstcall
141c-----------------------------------------------------------------------
142c   Computation of the soil temperatures using the Cgrd and Dgrd
143c  coefficient computed at the previous time-step:
144c  -----------------------------------------------
145
146c    surface temperature
147         DO ig=1,knon
148            ptsoil(ig,1)=(lambda*zc(ig,1)+ptsrf(ig))/
149     s      (lambda*(1.-zd(ig,1))+1.)
150         ENDDO
151
152c   other temperatures
153         DO jk=1,nsoilmx-1
154            DO ig=1,knon
155               ptsoil(ig,jk+1)=zc(ig,jk)+zd(ig,jk)*ptsoil(ig,jk)
156            ENDDO
157         ENDDO
158
159      ENDIF !--not firstcall
160c-----------------------------------------------------------------------
161c   Computation of the Cgrd and Dgrd coefficient for the next step:
162c   ---------------------------------------------------------------
163
164      DO jk=1,nsoilmx
165         zdz2(jk)=dz2(jk)/ptimestep
166      ENDDO
167
168      DO ig=1,knon
169         z1(ig)=zdz2(nsoilmx)+dz1(nsoilmx-1)
170         zc(ig,nsoilmx-1)=
171     $       zdz2(nsoilmx)*ptsoil(ig,nsoilmx)/z1(ig)
172         zd(ig,nsoilmx-1)=dz1(nsoilmx-1)/z1(ig)
173      ENDDO
174
175      DO jk=nsoilmx-1,2,-1
176         DO ig=1,knon
177            z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)
178     $         *(1.-zd(ig,jk)))
179            zc(ig,jk-1)=
180     s      (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))
181     $          *z1(ig)
182            zd(ig,jk-1)=dz1(jk-1)*z1(ig)
183         ENDDO
184      ENDDO
185
186c-----------------------------------------------------------------------
187c   computation of the surface diffusive flux from ground and
188c   calorific capacity of the ground:
189c   ---------------------------------
190
191      DO ig=1,knon
192         pfluxgrd(ig)=ztherm_i(ig)*dz1(1)*
193     s   (zc(ig,1)+(zd(ig,1)-1.)*ptsoil(ig,1))
194         pcapcal(ig)=ztherm_i(ig)*
195     s   (dz2(1)+ptimestep*(1.-zd(ig,1))*dz1(1))
196         z1(ig)=lambda*(1.-zd(ig,1))+1.
197         pcapcal(ig)=pcapcal(ig)/z1(ig)
198         pfluxgrd(ig) = pfluxgrd(ig)
199     s   + pcapcal(ig) * (ptsoil(ig,1) * z1(ig)
200     $       - lambda * zc(ig,1)
201     $       - ptsrf(ig))
202     s   /ptimestep
203      ENDDO
204
205      RETURN
206      END
Note: See TracBrowser for help on using the repository browser.