/[lmdze]/trunk/Sources/phylmd/Interface_surf/soil.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/Interface_surf/soil.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 157 by guez, Mon Jul 20 16:01:49 2015 UTC revision 175 by guez, Fri Feb 5 16:02:34 2016 UTC
# Line 4  module soil_m Line 4  module soil_m
4    
5  contains  contains
6    
7    SUBROUTINE soil(ptimestep, indice, knon, snow, ptsrf, ptsoil, pcapcal, &    SUBROUTINE soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
        pfluxgrd)  
8    
9      ! From LMDZ4/libf/phylmd/soil.F, version 1.1.1.1 2004/05/19      ! From LMDZ4/libf/phylmd/soil.F, version 1.1.1.1 2004/05/19
10    
11      USE dimens_m      ! Author: Frederic Hourdin 30/01/92
     USE indicesol  
     USE dimphy  
     USE dimsoil  
     USE suphec_m  
   
     ! =======================================================================  
   
     ! Auteur:  Frederic Hourdin     30/01/92  
     ! -------  
   
     ! objet:  computation of : the soil temperature evolution  
     ! ------                   the surfacic heat capacity "Capcal"  
     ! the surface conduction flux pcapcal  
12    
13        ! Object: computation of the soil temperature evolution, the
14        ! surfacic heat capacity "Soilcap" and the surface conduction flux
15    
16      ! Method: implicit time integration      ! Method: implicit time integration
17      ! -------  
18      ! Consecutive ground temperatures are related by:      ! Consecutive ground temperatures are related by:
19      ! T(k+1) = C(k) + D(k)*T(k)  (1)      ! T(k+1) = C(k) + D(k)*T(k) (1)
20      ! the coefficients C and D are computed at the t-dt time-step.      ! the coefficients C and D are computed at the t-dt time-step.
21      ! Routine structure:      ! Routine structure:
22      ! 1)new temperatures are computed  using (1)      ! 1) new temperatures are computed using (1)
23      ! 2)C and D coefficients are computed from the new temperature      ! 2) C and D coefficients are computed from the new temperature
24      ! profile for the t+dt time-step      ! profile for the t+dt time-step
25      ! 3)the coefficients A and B are computed where the diffusive      ! 3) the coefficients A and B are computed where the diffusive
26      ! fluxes at the t+dt time-step is given by      ! fluxes at the t+dt time-step is given by
27      ! Fdiff = A + B Ts(t+dt)      ! Fdiff = A + B Ts(t+dt)
28      ! or     Fdiff = F0 + Capcal (Ts(t+dt)-Ts(t))/dt      ! or Fdiff = F0 + Soilcap (Ts(t+dt)-Ts(t))/dt
29      ! with F0 = A + B (Ts(t))      ! with F0 = A + B (Ts(t))
30      ! Capcal = B*dt      ! Soilcap = B*dt
31    
32        USE dimens_m, only:
33        USE indicesol
34        USE dimphy
35        USE dimsoil
36        USE suphec_m
37    
38      ! Interface:      ! Interface:
39      ! ----------      ! ----------
40    
41      ! Arguments:      ! Arguments:
42      ! ----------      ! ----------
43      ! ptimestep            physical timestep (s)      ! dtime physical timestep (s)
44      ! indice               sub-surface index      ! indice sub-surface index
45      ! snow(klon,nbsrf)     snow      ! snow(klon, nbsrf) snow
46      ! ptsrf(knon)          surface temperature at time-step t (K)      ! tsurf(knon) surface temperature at time-step t (K)
47      ! ptsoil(klon,nsoilmx) temperature inside the ground (K)      ! tsoil(klon, nsoilmx) temperature inside the ground (K)
48      ! pcapcal(klon)        surfacic specific heat (W*m-2*s*K-1)      ! soilcap(klon) surfacic specific heat (W*m-2*s*K-1)
49      ! pfluxgrd(klon)       surface diffusive flux from ground (Wm-2)      ! soilflux(klon) surface diffusive flux from ground (Wm-2)
50    
     ! =======================================================================  
51      ! declarations:      ! declarations:
52      ! -------------      ! -------------
53    
   
54      ! -----------------------------------------------------------------------      ! -----------------------------------------------------------------------
55      ! arguments      ! arguments
56      ! ---------      ! ---------
57    
58      REAL ptimestep      REAL dtime
59      INTEGER indice, knon      INTEGER nisurf, knon
60      REAL ptsrf(knon), ptsoil(klon, nsoilmx), snow(klon)      REAL tsurf(knon), tsoil(klon, nsoilmx), snow(klon)
61      REAL pcapcal(klon), pfluxgrd(klon)      REAL soilcap(klon), soilflux(klon)
62    
63      ! -----------------------------------------------------------------------      ! -----------------------------------------------------------------------
64      ! local arrays      ! local arrays
65      ! ------------      ! ------------
66    
67      INTEGER ig, jk      INTEGER ig, jk
68      ! $$$      REAL zdz2(nsoilmx),z1(klon)      ! $$$ REAL zdz2(nsoilmx), z1(klon)
69      REAL zdz2(nsoilmx), z1(klon, nbsrf)      REAL zdz2(nsoilmx), z1(klon, nbsrf)
70      REAL min_period, dalph_soil      REAL min_period, dalph_soil
71      REAL ztherm_i(klon)      REAL ztherm_i(klon)
# Line 81  contains Line 73  contains
73      ! local saved variables:      ! local saved variables:
74      ! ----------------------      ! ----------------------
75      REAL dz1(nsoilmx), dz2(nsoilmx)      REAL dz1(nsoilmx), dz2(nsoilmx)
76      ! $$$          REAL zc(klon,nsoilmx),zd(klon,nsoilmx)      ! $$$ REAL zc(klon, nsoilmx), zd(klon, nsoilmx)
77      REAL zc(klon, nsoilmx, nbsrf), zd(klon, nsoilmx, nbsrf)      REAL zc(klon, nsoilmx, nbsrf), zd(klon, nsoilmx, nbsrf)
78      REAL lambda      REAL lambda
79      SAVE dz1, dz2, zc, zd, lambda      SAVE dz1, dz2, zc, zd, lambda
# Line 100  contains Line 92  contains
92    
93      REAL rk, fz1, rk1, rk2      REAL rk, fz1, rk1, rk2
94    
95      pfluxgrd(:) = 0.      soilflux(:) = 0.
96      ! calcul de l'inertie thermique a partir de la variable rnat.      ! calcul de l'inertie thermique a partir de la variable rnat.
97      ! on initialise a iice meme au-dessus d'un point de mer au cas      ! on initialise a iice meme au-dessus d'un point de mer au cas
98      ! ou le point de mer devienne point de glace au pas suivant      ! ou le point de mer devienne point de glace au pas suivant
99      ! on corrige si on a un point de terre avec ou sans glace      ! on corrige si on a un point de terre avec ou sans glace
100    
101      IF (indice==is_sic) THEN      IF (nisurf==is_sic) THEN
102         DO ig = 1, knon         DO ig = 1, knon
103            ztherm_i(ig) = iice            ztherm_i(ig) = iice
104            IF (snow(ig)>0.0) ztherm_i(ig) = isno            IF (snow(ig)>0.0) ztherm_i(ig) = isno
105         END DO         END DO
106      ELSE IF (indice==is_lic) THEN      ELSE IF (nisurf==is_lic) THEN
107         DO ig = 1, knon         DO ig = 1, knon
108            ztherm_i(ig) = iice            ztherm_i(ig) = iice
109            IF (snow(ig)>0.0) ztherm_i(ig) = isno            IF (snow(ig)>0.0) ztherm_i(ig) = isno
110         END DO         END DO
111      ELSE IF (indice==is_ter) THEN      ELSE IF (nisurf==is_ter) THEN
112         DO ig = 1, knon         DO ig = 1, knon
113            ztherm_i(ig) = isol            ztherm_i(ig) = isol
114            IF (snow(ig)>0.0) ztherm_i(ig) = isno            IF (snow(ig)>0.0) ztherm_i(ig) = isno
115         END DO         END DO
116      ELSE IF (indice==is_oce) THEN      ELSE IF (nisurf==is_oce) THEN
117         DO ig = 1, knon         DO ig = 1, knon
118            ztherm_i(ig) = iice            ztherm_i(ig) = iice
119         END DO         END DO
120      ELSE      ELSE
121         PRINT *, 'valeur d indice non prevue', indice         PRINT *, 'valeur d indice non prevue', nisurf
122         STOP 1         STOP 1
123      END IF      END IF
124    
125      IF (firstsurf(indice)) THEN      IF (firstsurf(nisurf)) THEN
126    
127         ! -----------------------------------------------------------------------         ! -----------------------------------------------------------------------
128         ! ground levels         ! ground levels
# Line 144  contains Line 136  contains
136         READ (99, *) min_period         READ (99, *) min_period
137         READ (99, *) dalph_soil         READ (99, *) dalph_soil
138         PRINT *, 'Discretization for the soil model'         PRINT *, 'Discretization for the soil model'
139         PRINT *, 'First level e-folding depth', min_period, '   dalph', &         PRINT *, 'First level e-folding depth', min_period, ' dalph', &
140              dalph_soil              dalph_soil
141         CLOSE (99)         CLOSE (99)
142  9999   CONTINUE  9999   CONTINUE
# Line 171  contains Line 163  contains
163            PRINT *, 'fz=', fz(rk1)*fz(rk2)*3.14, fz(rk)*fz(rk)*3.14            PRINT *, 'fz=', fz(rk1)*fz(rk2)*3.14, fz(rk)*fz(rk)*3.14
164         END DO         END DO
165         ! PB         ! PB
166         firstsurf(indice) = .FALSE.         firstsurf(nisurf) = .FALSE.
167    
168         ! Initialisations:         ! Initialisations:
169         ! ----------------         ! ----------------
# Line 184  contains Line 176  contains
176    
177         ! surface temperature         ! surface temperature
178         DO ig = 1, knon         DO ig = 1, knon
179            ptsoil(ig, 1) = (lambda*zc(ig,1,indice)+ptsrf(ig))/(lambda*(1.-zd(ig,1, &            tsoil(ig, 1) = (lambda*zc(ig, 1, nisurf)+tsurf(ig))/(lambda*(1.-zd(ig, 1, &
180                 indice))+1.)                 nisurf))+1.)
181         END DO         END DO
182    
183         ! other temperatures         ! other temperatures
184         DO jk = 1, nsoilmx - 1         DO jk = 1, nsoilmx - 1
185            DO ig = 1, knon            DO ig = 1, knon
186               ptsoil(ig, jk+1) = zc(ig, jk, indice) + zd(ig, jk, indice)*ptsoil(ig, &               tsoil(ig, jk+1) = zc(ig, jk, nisurf) + zd(ig, jk, nisurf)*tsoil(ig, &
187                    jk)                    jk)
188            END DO            END DO
189         END DO         END DO
# Line 201  contains Line 193  contains
193      ! Computation of the Cgrd and Dgrd coefficient for the next step:      ! Computation of the Cgrd and Dgrd coefficient for the next step:
194      ! ---------------------------------------------------------------      ! ---------------------------------------------------------------
195    
196      ! $$$  PB ajout pour cas glace de mer      ! $$$ PB ajout pour cas glace de mer
197      IF (indice==is_sic) THEN      IF (nisurf==is_sic) THEN
198         DO ig = 1, knon         DO ig = 1, knon
199            ptsoil(ig, nsoilmx) = rtt - 1.8            tsoil(ig, nsoilmx) = rtt - 1.8
200         END DO         END DO
201      END IF      END IF
202    
203      DO jk = 1, nsoilmx      DO jk = 1, nsoilmx
204         zdz2(jk) = dz2(jk)/ptimestep         zdz2(jk) = dz2(jk)/dtime
205      END DO      END DO
206    
207      DO ig = 1, knon      DO ig = 1, knon
208         z1(ig, indice) = zdz2(nsoilmx) + dz1(nsoilmx-1)         z1(ig, nisurf) = zdz2(nsoilmx) + dz1(nsoilmx-1)
209         zc(ig, nsoilmx-1, indice) = zdz2(nsoilmx)*ptsoil(ig, nsoilmx)/ &         zc(ig, nsoilmx-1, nisurf) = zdz2(nsoilmx)*tsoil(ig, nsoilmx)/ &
210              z1(ig, indice)              z1(ig, nisurf)
211         zd(ig, nsoilmx-1, indice) = dz1(nsoilmx-1)/z1(ig, indice)         zd(ig, nsoilmx-1, nisurf) = dz1(nsoilmx-1)/z1(ig, nisurf)
212      END DO      END DO
213    
214      DO jk = nsoilmx - 1, 2, -1      DO jk = nsoilmx - 1, 2, -1
215         DO ig = 1, knon         DO ig = 1, knon
216            z1(ig, indice) = 1./(zdz2(jk)+dz1(jk-1)+dz1(jk)*(1.-zd(ig,jk,indice)))            z1(ig, nisurf) = 1./(zdz2(jk)+dz1(jk-1)+dz1(jk)*(1.-zd(ig, jk, nisurf)))
217            zc(ig, jk-1, indice) = (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk,indice) &            zc(ig, jk-1, nisurf) = (tsoil(ig, jk)*zdz2(jk)+dz1(jk)*zc(ig, jk, nisurf) &
218                 )*z1(ig, indice)                 )*z1(ig, nisurf)
219            zd(ig, jk-1, indice) = dz1(jk-1)*z1(ig, indice)            zd(ig, jk-1, nisurf) = dz1(jk-1)*z1(ig, nisurf)
220         END DO         END DO
221      END DO      END DO
222    
# Line 234  contains Line 226  contains
226      ! ---------------------------------      ! ---------------------------------
227    
228      DO ig = 1, knon      DO ig = 1, knon
229         pfluxgrd(ig) = ztherm_i(ig)*dz1(1)*(zc(ig,1,indice)+(zd(ig,1, &         soilflux(ig) = ztherm_i(ig)*dz1(1)*(zc(ig, 1, nisurf)+(zd(ig, 1, &
230              indice)-1.)*ptsoil(ig,1))              nisurf)-1.)*tsoil(ig, 1))
231         pcapcal(ig) = ztherm_i(ig)*(dz2(1)+ptimestep*(1.-zd(ig,1,indice))*dz1(1))         soilcap(ig) = ztherm_i(ig)*(dz2(1)+dtime*(1.-zd(ig, 1, nisurf))*dz1(1))
232         z1(ig, indice) = lambda*(1.-zd(ig,1,indice)) + 1.         z1(ig, nisurf) = lambda*(1.-zd(ig, 1, nisurf)) + 1.
233         pcapcal(ig) = pcapcal(ig)/z1(ig, indice)         soilcap(ig) = soilcap(ig)/z1(ig, nisurf)
234         pfluxgrd(ig) = pfluxgrd(ig) + pcapcal(ig)*(ptsoil(ig,1)*z1(ig,indice)- &         soilflux(ig) = soilflux(ig) + soilcap(ig)*(tsoil(ig, 1)*z1(ig, nisurf)- &
235              lambda*zc(ig,1,indice)-ptsrf(ig))/ptimestep              lambda*zc(ig, 1, nisurf)-tsurf(ig))/dtime
236      END DO      END DO
237    
238    contains    contains

Legend:
Removed from v.157  
changed lines
  Added in v.175

  ViewVC Help
Powered by ViewVC 1.1.21