source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/phymars/soil.F @ 1242

Last change on this file since 1242 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 5.7 KB
Line 
1      SUBROUTINE soil(ngrid,nsoil,firstcall,ptherm_i,
2     s          ptimestep,ptsrf,ptsoil,
3     s          pcapcal,pfluxgrd)
4      IMPLICIT NONE
5
6c=======================================================================
7c
8c   Auteur:  Frederic Hourdin     30/01/92
9c   -------
10c
11c   objet:  computation of : the soil temperature evolution
12c   ------                   the surfacic heat capacity "Capcal"
13c                            the surface conduction flux pcapcal
14c
15c
16c   Method: implicit time integration
17c   -------
18c   Consecutive ground temperatures are related by:
19c           T(k+1) = C(k) + D(k)*T(k)  (1)
20c   the coefficients C and D are computed at the t-dt time-step.
21c   Routine structure:
22c   1)new temperatures are computed  using (1)
23c   2)C and D coefficients are computed from the new temperature
24c     profile for the t+dt time-step
25c   3)the coefficients A and B are computed where the diffusive
26c     fluxes at the t+dt time-step is given by
27c            Fdiff = A + B Ts(t+dt)
28c     or     Fdiff = F0 + Capcal (Ts(t+dt)-Ts(t))/dt
29c            with F0 = A + B (Ts(t))
30c                 Capcal = B*dt
31c           
32c   Interface:
33c   ----------
34c
35c   Arguments:
36c   ----------
37c   ngird               number of grid-points
38c   ptimestep              physical timestep (s)
39c   pto(ngrid,nsoil)     temperature at time-step t (K)
40c   ptn(ngrid,nsoil)     temperature at time step t+dt (K)
41c   pcapcal(ngrid)      specific heat (W*m-2*s*K-1)
42c   pfluxgrd(ngrid)      surface diffusive flux from ground (Wm-2)
43c   
44c=======================================================================
45c   declarations:
46c   -------------
47
48#include "dimensions.h"
49#include "dimphys.h"
50
51c-----------------------------------------------------------------------
52c  arguments
53c  ---------
54
55      INTEGER ngrid,nsoil
56      REAL ptimestep
57      REAL ptsrf(ngridmx),ptsoil(ngrid,nsoilmx),ptherm_i(ngridmx)
58      REAL pcapcal(ngrid),pfluxgrd(ngrid)
59      LOGICAL firstcall
60
61c-----------------------------------------------------------------------
62c  local arrays
63c  ------------
64
65      INTEGER ig,jk
66      REAL za(ngridmx),zb(ngridmx)
67      REAL zdz2(nsoilmx),z1(ngridmx)
68      REAL min_period,dalph_soil
69
70c   local saved variables:
71c   ----------------------
72      REAL dz1(nsoilmx),dz2(nsoilmx)
73      REAL zc(ngridmx,nsoilmx),zd(ngridmx,nsoilmx)
74      REAL lambda
75      SAVE dz1,dz2,zc,zd,lambda
76
77c-----------------------------------------------------------------------
78c   Depthts:
79c   --------
80
81      REAL fz,rk,fz1,rk1,rk2
82      fz(rk)=fz1*(dalph_soil**rk-1.)/(dalph_soil-1.)
83
84      IF (firstcall) THEN
85
86c-----------------------------------------------------------------------
87c   ground levels
88c   grnd=z/l where l is the skin depth of the diurnal cycle:
89c   --------------------------------------------------------
90
91         min_period=887.75
92c        min_period=1800.
93c        min_period=20000.
94         dalph_soil=2.
95
96         OPEN(99,file='soil.def',status='old',form='formatted',err=9999)
97         READ(99,*) min_period
98         READ(99,*) dalph_soil
99         PRINT*,'Discretization for the soil model'
100         PRINT*,'First level e-folding depth',min_period,
101     s   '   dalph',dalph_soil
102         CLOSE(99)
1039999     CONTINUE
104
105c   la premiere couche represente un dixieme de cycle diurne
106         fz1=sqrt(min_period/3.14)
107
108         DO jk=1,nsoil
109            rk1=jk
110            rk2=jk-1
111            dz2(jk)=fz(rk1)-fz(rk2)
112         ENDDO
113         DO jk=1,nsoil-1
114            rk1=jk+.5
115            rk2=jk-.5
116            dz1(jk)=1./(fz(rk1)-fz(rk2))
117         ENDDO
118         lambda=fz(.5)*dz1(1)
119         PRINT*,'full layers, intermediate layers (secoonds)'
120         DO jk=1,nsoil
121            rk=jk
122            rk1=jk+.5
123            rk2=jk-.5
124            PRINT*,fz(rk1)*fz(rk2)*3.14,
125     s      fz(rk)*fz(rk)*3.14
126         ENDDO
127
128c   Initialisations:
129c   ----------------
130
131      ELSE
132c-----------------------------------------------------------------------
133c   Computation of the soil temperatures using the Cgrd and Dgrd
134c  coefficient computed at the previous time-step:
135c  -----------------------------------------------
136
137c    surface temperature
138         DO ig=1,ngrid
139            ptsoil(ig,1)=(lambda*zc(ig,1)+ptsrf(ig))/
140     s      (lambda*(1.-zd(ig,1))+1.)
141         ENDDO
142
143c   other temperatures
144         DO jk=1,nsoil-1
145            DO ig=1,ngrid
146               ptsoil(ig,jk+1)=zc(ig,jk)+zd(ig,jk)*ptsoil(ig,jk)
147            ENDDO
148         ENDDO
149
150      ENDIF
151c-----------------------------------------------------------------------
152c   Computation of the Cgrd and Dgrd coefficient for the next step:
153c   ---------------------------------------------------------------
154
155      DO jk=1,nsoil
156         zdz2(jk)=dz2(jk)/ptimestep
157      ENDDO
158
159      DO ig=1,ngrid
160         z1(ig)=zdz2(nsoil)+dz1(nsoil-1)
161         zc(ig,nsoil-1)=zdz2(nsoil)*ptsoil(ig,nsoil)/z1(ig)
162         zd(ig,nsoil-1)=dz1(nsoil-1)/z1(ig)
163      ENDDO
164
165      DO jk=nsoil-1,2,-1
166         DO ig=1,ngrid
167            z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)*(1.-zd(ig,jk)))
168            zc(ig,jk-1)=
169     s      (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))*z1(ig)
170            zd(ig,jk-1)=dz1(jk-1)*z1(ig)
171         ENDDO
172      ENDDO
173
174c-----------------------------------------------------------------------
175c   computation of the surface diffusive flux from ground and
176c   calorific capacity of the ground:
177c   ---------------------------------
178
179      DO ig=1,ngrid
180         pfluxgrd(ig)=ptherm_i(ig)*dz1(1)*
181     s   (zc(ig,1)+(zd(ig,1)-1.)*ptsoil(ig,1))
182         pcapcal(ig)=ptherm_i(ig)*
183     s   (dz2(1)+ptimestep*(1.-zd(ig,1))*dz1(1))
184         z1(ig)=lambda*(1.-zd(ig,1))+1.
185         pcapcal(ig)=pcapcal(ig)/z1(ig)
186         pfluxgrd(ig)=pfluxgrd(ig)
187     s   +pcapcal(ig)*(ptsoil(ig,1)*z1(ig)-lambda*zc(ig,1)-ptsrf(ig))
188     s   /ptimestep
189      ENDDO
190
191      RETURN
192      END
Note: See TracBrowser for help on using the repository browser.