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

Last change on this file since 1661 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

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 "YOMCST.h"
51#include "dimsoil.h"
52#include "clesphys.h"
53
54c-----------------------------------------------------------------------
55c  arguments
56c  ---------
57
58      REAL ptimestep
59      INTEGER knon
60      REAL ptsrf(klon),ptsoil(klon,nsoilmx)
61      REAL pcapcal(klon),pfluxgrd(klon)
62
63c-----------------------------------------------------------------------
64c  local arrays
65c  ------------
66
67      INTEGER ig,jk
68      REAL zdz2(nsoilmx),z1(klon)
69      REAL min_period,dalph_soil
70      REAL ztherm_i(klon)
71
72c   local saved variables:
73c   ----------------------
74      REAL dz1(nsoilmx),dz2(nsoilmx)
75      REAL,allocatable :: zc(:,:),zd(:,:)
76      REAL lambda
77      SAVE dz1,dz2,zc,zd,lambda
78      LOGICAL firstcall
79      SAVE firstcall
80
81      DATA firstcall/.true./
82
83c-----------------------------------------------------------------------
84c   Depthts:
85c   --------
86
87      REAL fz,rk,fz1,rk1,rk2
88      fz(rk)=fz1*(dalph_soil**rk-1.)/(dalph_soil-1.)
89      pfluxgrd(:) = 0.
90 
91      DO ig = 1, knon
92          ztherm_i(ig)   = inertie
93      ENDDO
94
95      IF (firstcall) THEN
96
97      allocate(zc(klon,nsoilmx),zd(klon,nsoilmx))
98
99c-----------------------------------------------------------------------
100c   ground levels
101c   grnd=z/l where l is the skin depth of the diurnal cycle:
102c   --------------------------------------------------------
103
104c VENUS : A REVOIR !!!!
105         min_period=20000. ! en secondes
106         dalph_soil=2.    ! rapport entre les epaisseurs de 2 couches succ.
107
108         OPEN(99,file='soil.def',status='old',form='formatted',err=9999)
109         READ(99,*) min_period
110         READ(99,*) dalph_soil
111         PRINT*,'Discretization for the soil model'
112         PRINT*,'First level e-folding depth',min_period,
113     s   '   dalph',dalph_soil
114         CLOSE(99)
1159999     CONTINUE
116
117c   la premiere couche represente un dixieme de cycle diurne
118         fz1=sqrt(min_period/3.14)
119
120         DO jk=1,nsoilmx
121            rk1=jk
122            rk2=jk-1
123            dz2(jk)=fz(rk1)-fz(rk2)
124         ENDDO
125         DO jk=1,nsoilmx-1
126            rk1=jk+.5
127            rk2=jk-.5
128            dz1(jk)=1./(fz(rk1)-fz(rk2))
129         ENDDO
130         lambda=fz(.5)*dz1(1)
131         PRINT*,'full layers, intermediate layers (seconds)'
132         DO jk=1,nsoilmx
133            rk=jk
134            rk1=jk+.5
135            rk2=jk-.5
136            PRINT *,'fz=',
137     .               fz(rk1)*fz(rk2)*3.14,fz(rk)*fz(rk)*3.14
138         ENDDO
139         firstcall =.false.
140
141      ELSE   !--not firstcall
142c-----------------------------------------------------------------------
143c   Computation of the soil temperatures using the Cgrd and Dgrd
144c  coefficient computed at the previous time-step:
145c  -----------------------------------------------
146
147c    surface temperature
148         DO ig=1,knon
149            ptsoil(ig,1)=(lambda*zc(ig,1)+ptsrf(ig))/
150     s      (lambda*(1.-zd(ig,1))+1.)
151         ENDDO
152
153c   other temperatures
154         DO jk=1,nsoilmx-1
155            DO ig=1,knon
156               ptsoil(ig,jk+1)=zc(ig,jk)+zd(ig,jk)*ptsoil(ig,jk)
157            ENDDO
158         ENDDO
159
160      ENDIF !--not firstcall
161c-----------------------------------------------------------------------
162c   Computation of the Cgrd and Dgrd coefficient for the next step:
163c   ---------------------------------------------------------------
164
165      DO jk=1,nsoilmx
166         zdz2(jk)=dz2(jk)/ptimestep
167      ENDDO
168
169      DO ig=1,knon
170         z1(ig)=zdz2(nsoilmx)+dz1(nsoilmx-1)
171         zc(ig,nsoilmx-1)=
172     $       zdz2(nsoilmx)*ptsoil(ig,nsoilmx)/z1(ig)
173         zd(ig,nsoilmx-1)=dz1(nsoilmx-1)/z1(ig)
174      ENDDO
175
176      DO jk=nsoilmx-1,2,-1
177         DO ig=1,knon
178            z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)
179     $         *(1.-zd(ig,jk)))
180            zc(ig,jk-1)=
181     s      (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))
182     $          *z1(ig)
183            zd(ig,jk-1)=dz1(jk-1)*z1(ig)
184         ENDDO
185      ENDDO
186
187c-----------------------------------------------------------------------
188c   computation of the surface diffusive flux from ground and
189c   calorific capacity of the ground:
190c   ---------------------------------
191
192      DO ig=1,knon
193         pfluxgrd(ig)=ztherm_i(ig)*dz1(1)*
194     s   (zc(ig,1)+(zd(ig,1)-1.)*ptsoil(ig,1))
195         pcapcal(ig)=ztherm_i(ig)*
196     s   (dz2(1)+ptimestep*(1.-zd(ig,1))*dz1(1))
197         z1(ig)=lambda*(1.-zd(ig,1))+1.
198         pcapcal(ig)=pcapcal(ig)/z1(ig)
199         pfluxgrd(ig) = pfluxgrd(ig)
200     s   + pcapcal(ig) * (ptsoil(ig,1) * z1(ig)
201     $       - lambda * zc(ig,1)
202     $       - ptsrf(ig))
203     s   /ptimestep
204      ENDDO
205
206      RETURN
207      END
Note: See TracBrowser for help on using the repository browser.