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

Last change on this file since 1240 was 101, checked in by slebonnois, 14 years ago

SL: modifications pour arriver a compiler le gcm VENUS !
Ca marche !
A noter: modifs de makelmdz

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
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
49      IMPLICIT NONE
50#include "dimensions.h"
51#include "YOMCST.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,allocatable :: zc(:,:),zd(:,:)
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
98      allocate(zc(klon,nsoilmx),zd(klon,nsoilmx))
99
100c-----------------------------------------------------------------------
101c   ground levels
102c   grnd=z/l where l is the skin depth of the diurnal cycle:
103c   --------------------------------------------------------
104
105c VENUS : A REVOIR !!!!
106         min_period=20000. ! en secondes
107         dalph_soil=2.    ! rapport entre les epaisseurs de 2 couches succ.
108
109         OPEN(99,file='soil.def',status='old',form='formatted',err=9999)
110         READ(99,*) min_period
111         READ(99,*) dalph_soil
112         PRINT*,'Discretization for the soil model'
113         PRINT*,'First level e-folding depth',min_period,
114     s   '   dalph',dalph_soil
115         CLOSE(99)
1169999     CONTINUE
117
118c   la premiere couche represente un dixieme de cycle diurne
119         fz1=sqrt(min_period/3.14)
120
121         DO jk=1,nsoilmx
122            rk1=jk
123            rk2=jk-1
124            dz2(jk)=fz(rk1)-fz(rk2)
125         ENDDO
126         DO jk=1,nsoilmx-1
127            rk1=jk+.5
128            rk2=jk-.5
129            dz1(jk)=1./(fz(rk1)-fz(rk2))
130         ENDDO
131         lambda=fz(.5)*dz1(1)
132         PRINT*,'full layers, intermediate layers (seconds)'
133         DO jk=1,nsoilmx
134            rk=jk
135            rk1=jk+.5
136            rk2=jk-.5
137            PRINT *,'fz=',
138     .               fz(rk1)*fz(rk2)*3.14,fz(rk)*fz(rk)*3.14
139         ENDDO
140         firstcall =.false.
141
142      ELSE   !--not firstcall
143c-----------------------------------------------------------------------
144c   Computation of the soil temperatures using the Cgrd and Dgrd
145c  coefficient computed at the previous time-step:
146c  -----------------------------------------------
147
148c    surface temperature
149         DO ig=1,knon
150            ptsoil(ig,1)=(lambda*zc(ig,1)+ptsrf(ig))/
151     s      (lambda*(1.-zd(ig,1))+1.)
152         ENDDO
153
154c   other temperatures
155         DO jk=1,nsoilmx-1
156            DO ig=1,knon
157               ptsoil(ig,jk+1)=zc(ig,jk)+zd(ig,jk)*ptsoil(ig,jk)
158            ENDDO
159         ENDDO
160
161      ENDIF !--not firstcall
162c-----------------------------------------------------------------------
163c   Computation of the Cgrd and Dgrd coefficient for the next step:
164c   ---------------------------------------------------------------
165
166      DO jk=1,nsoilmx
167         zdz2(jk)=dz2(jk)/ptimestep
168      ENDDO
169
170      DO ig=1,knon
171         z1(ig)=zdz2(nsoilmx)+dz1(nsoilmx-1)
172         zc(ig,nsoilmx-1)=
173     $       zdz2(nsoilmx)*ptsoil(ig,nsoilmx)/z1(ig)
174         zd(ig,nsoilmx-1)=dz1(nsoilmx-1)/z1(ig)
175      ENDDO
176
177      DO jk=nsoilmx-1,2,-1
178         DO ig=1,knon
179            z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)
180     $         *(1.-zd(ig,jk)))
181            zc(ig,jk-1)=
182     s      (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))
183     $          *z1(ig)
184            zd(ig,jk-1)=dz1(jk-1)*z1(ig)
185         ENDDO
186      ENDDO
187
188c-----------------------------------------------------------------------
189c   computation of the surface diffusive flux from ground and
190c   calorific capacity of the ground:
191c   ---------------------------------
192
193      DO ig=1,knon
194         pfluxgrd(ig)=ztherm_i(ig)*dz1(1)*
195     s   (zc(ig,1)+(zd(ig,1)-1.)*ptsoil(ig,1))
196         pcapcal(ig)=ztherm_i(ig)*
197     s   (dz2(1)+ptimestep*(1.-zd(ig,1))*dz1(1))
198         z1(ig)=lambda*(1.-zd(ig,1))+1.
199         pcapcal(ig)=pcapcal(ig)/z1(ig)
200         pfluxgrd(ig) = pfluxgrd(ig)
201     s   + pcapcal(ig) * (ptsoil(ig,1) * z1(ig)
202     $       - lambda * zc(ig,1)
203     $       - ptsrf(ig))
204     s   /ptimestep
205      ENDDO
206
207      RETURN
208      END
Note: See TracBrowser for help on using the repository browser.