source: dynamico_lmdz/simple_physics/phyparam/param/soil.F @ 4187

Last change on this file since 4187 was 4176, checked in by dubos, 5 years ago

simple_physics : copy code from FH

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