source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/phys/soil_settings.f @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 11.5 KB
Line 
1      subroutine soil_settings(nid,ngrid,nsoil,tsurf,tsoil,indextime)
2
3!      use netcdf
4      use comsoil_h, only: layer, mlayer, inertiedat, volcapa
5      use iostart, only: inquire_field_ndims, get_var, get_field,
6     &                   inquire_field, inquire_dimension_length
7      implicit none
8
9!======================================================================
10!  Author: Ehouarn Millour (07/2006)
11!
12!  Purpose: Read and/or initialise soil depths and properties
13!
14! Modifications: Aug.2010 EM : use NetCDF90 to load variables (enables using
15!                      r4 or r8 restarts independently of having compiled
16!                      the GCM in r4 or r8)
17!                June 2013 TN : Possibility to read files with a time axis
18!
19!
20!  This subroutine reads from a NetCDF file (opened by the caller)
21!  of "startfi.nc" format.
22!  The various actions and variable read/initialized are:
23!  1. Check out the number of soil layers (in datafile); if it isn't equal
24!     to nsoil, then some interpolation will be required
25!     Also check if data in file "startfi.nc" is in older format (ie:
26!     thermal inertia was depth-independent; and there was no "depth"
27!     coordinate.
28!     Read/build layer (and midlayer) depths
29!  2. Read volumetric specific heat (or initialise it to default value)
30!  3. Read Thermal inertia
31!  4. Read soil temperatures
32!  5. Interpolate thermal inertia and temperature on the new grid, if
33!     necessary
34!======================================================================
35
36!======================================================================
37!  arguments
38!  ---------
39!  inputs:
40      integer,intent(in) :: nid ! Input Netcdf file ID
41      integer,intent(in) :: ngrid       ! # of horizontal grid points
42      integer,intent(in) :: nsoil       ! # of soil layers
43      real,intent(in) :: tsurf(ngrid)   ! surface temperature
44      integer,intent(in) :: indextime   ! position on time axis
45!  output:
46      real,intent(out) :: tsoil(ngrid,nsoil)    ! soil temperature
47
48!======================================================================
49! local variables:
50      integer ierr      ! status (returned by NetCDF functions)
51      integer nvarid    ! ID of NetCDF variable
52      integer dimid     ! ID of NetCDF dimension
53      integer dimlen    ! length along the "depth" dimension
54      integer ndims     ! # of dimensions of read <inertiedat> data
55      integer ig,iloop  ! loop counters
56     
57      integer edges(3),corner(3) ! to read a specific time
58
59      logical :: olddepthdef=.false. ! flag
60      logical :: interpol=.false. ! flag: true if interpolation will be requiered
61
62      ! to store "old" values
63      real,dimension(:),allocatable :: surfinertia !surface thermal inertia
64      real,dimension(:),allocatable :: oldmlayer
65      real,dimension(:,:),allocatable :: oldinertiedat
66      real,dimension(:,:),allocatable :: oldtsoil
67      ! for interpolation
68      real,dimension(:),allocatable :: oldgrid
69      real,dimension(:),allocatable :: oldval
70      real,dimension(:),allocatable :: newval
71
72      real alpha,lay1 ! coefficients for building layers
73      real xmin,xmax ! to display min and max of a field
74
75      real,parameter :: default_volcapa=1.e6
76
77      logical :: found,ok
78!======================================================================
79! 1. Depth coordinate
80! -------------------
81! 1.1 Start by reading how many layers of soil there are
82        dimlen=inquire_dimension_length("subsurface_layers")
83
84        if (dimlen.ne.nsoil) then
85          write(*,*)'soil_settings: Interpolation of soil temperature ',
86     &              'and thermal inertia will be required!'
87        ! if dimlen doesn't match nsoil, then interpolation of
88        ! soil temperatures and thermal inertia will be requiered
89          interpol=.true.
90        endif
91! 1.2 Find out the # of dimensions <inertiedat> was defined as using
92      ndims=inquire_field_ndims("inertiedat")
93! 1.3 Read depths values or set olddepthdef flag and values
94      if (ndims.eq.1) then ! we know that there is none
95        write(*,*)'soil_settings: no <soildepth> field expected'
96        write(*,*)'building one mimicking old definitions'
97        olddepthdef=.true.
98        interpol=.true.
99        ! allocate oldmlayer
100        if (.not.allocated(oldmlayer)) then
101          allocate(oldmlayer(dimlen),stat=ierr)
102          if (ierr.ne.0) then
103            write(*,*) 'soil_settings: failed allocation of oldmlayer!'
104            stop
105          endif
106        endif
107        do iloop=1,dimlen
108          oldmlayer(iloop)=sqrt(887.75/3.14)*((2.**(iloop-0.5))-1.)
109        enddo
110      else ! Look for depth
111        ! read <depth> coordinate
112        if (interpol) then !put values in oldmlayer
113          call get_var("soildepth",oldmlayer,found)
114          if (.not.found) then
115            write(*,*)'soil_settings: Problem while reading <soildepth>'
116          endif
117        else ! put values in mlayer
118          call get_var("soildepth",mlayer,found)
119          print*,"mlayer",mlayer
120          if (.not.found) then
121            write(*,*)'soil_settings: Problem while reading <soildepth>'
122          endif
123        endif !of if (interpol)
124      endif !of if (ndims.eq.1)
125! 1.4 Build mlayer(), if necessary
126      if (interpol) then
127      ! default mlayer distribution, following a power law:
128      !  mlayer(k)=lay1*alpha**(k-1/2)
129        lay1=2.e-4
130        alpha=2
131        do iloop=0,nsoil-1
132          mlayer(iloop)=lay1*(alpha**(iloop-0.5))
133        enddo
134      endif
135! 1.5 Build layer(); following the same law as mlayer()
136      ! Assuming layer distribution follows mid-layer law:
137      ! layer(k)=lay1*alpha**(k-1)
138      lay1=sqrt(mlayer(0)*mlayer(1))
139      alpha=mlayer(1)/mlayer(0)
140      do iloop=1,nsoil
141        layer(iloop)=lay1*(alpha**(iloop-1))
142      enddo
143! 2. Volumetric heat capacity (note: it is declared in comsoil_h)
144! ---------------------------
145! "volcapa" is (so far) 0D and written in "controle" table of startfi file
146! volcapa is read or set when "controle" is read (see tabfi.F)
147! Just in case, we check here that it is not zero. If it is, we
148! set it to "default_volcapa"
149
150      if (volcapa.le.0.0) then
151        write(*,*)'soil_settings: Warning, volcapa = ',volcapa
152        write(*,*)'               That doesn t seem right'
153        write(*,*)'        Initializing Volumetric heat capacity to ',
154     &             default_volcapa
155        volcapa=default_volcapa
156      endif
157
158! 3. Thermal inertia (note: it is declared in comsoil_h)
159! ------------------
160! 3.1 Look (again) for thermal inertia data (to reset nvarid)
161
162! 3.2 Knowing the # of dimensions <inertidat> was defined as using,
163!     read/build thermal inertia
164
165      if (ndims.eq.1) then ! "old 2D-surface" format
166       write(*,*)'soil_settings: Thermal inertia is only given as surfac
167     &e data!'
168       ! Read Surface thermal inertia
169       allocate(surfinertia(ngrid))
170       call get_field("inertiedat",surfinertia,found)
171       if (.not.found) then
172         write(*,*) "soil_settings: Failed loading <inertiedat>"
173         call abort
174       endif
175       
176       write(*,*)' => Building soil thermal inertia (using reference sur
177     &face thermal inertia)'
178       do iloop=1,nsoil
179         inertiedat(:,iloop)=surfinertia(:)
180       enddo
181       deallocate(surfinertia)
182
183      else ! "3D surface+depth" format
184       if (interpol) then ! put values in oldinertiedat
185         if (.not.allocated(oldinertiedat)) then
186           allocate(oldinertiedat(ngrid,dimlen),stat=ierr)
187           if (ierr.ne.0) then
188            write(*,*) 'soil_settings: failed allocation of ',
189     &                 'oldinertiedat!'
190            stop
191           endif
192         endif ! of if (.not.allocated(oldinertiedat))
193        call get_field("inertiedat",oldinertiedat,found)
194        if (.not.found) then
195          write(*,*) "soil_settings: Failed loading <inertiedat>"
196          call abort
197        endif
198       else ! put values in therm_i
199         call get_field("inertiedat",inertiedat,found)
200         if (.not.found) then
201           write(*,*) "soil_settings: Failed loading <inertiedat>"
202           call abort
203         endif
204!        endif
205       endif ! of if (interpol)
206      endif ! of if (ndims.eq.1)
207     
208! 4. Read soil temperatures
209! -------------------------
210!      ierr=nf90_inq_varid(nid,"tsoil",nvarid)
211      ok=inquire_field("tsoil")
212!      if (ierr.ne.nf90_noerr) then
213      if (.not.ok) then
214        write(*,*)'soil_settings: Field <tsoil> not found!'
215        write(*,*)' => Building <tsoil> from surface values <tsurf>'
216        do iloop=1,nsoil
217          tsoil(:,iloop)=tsurf(:)
218        enddo
219      else ! <tsoil> found
220       if (interpol) then ! put values in oldtsoil
221         if (.not.allocated(oldtsoil)) then
222           allocate(oldtsoil(ngrid,dimlen),stat=ierr)
223           if (ierr.ne.0) then
224             write(*,*) 'soil_settings: failed allocation of ',
225     &                  'oldtsoil!'
226             stop
227           endif
228         endif
229         call get_field("tsoil",oldtsoil,found)
230         if (.not.found) then
231           write(*,*) "soil_settings: Failed loading <tsoil>"
232           call abort
233         endif
234       else ! put values in tsoil
235         call get_field("tsoil",tsoil,found,timeindex=indextime)
236         if (.not.found) then
237           write(*,*) "soil_settings: Failed loading <tsoil>"
238           call abort
239         endif
240       endif ! of if (interpol)
241      endif! of if (.not.ok)
242
243! 5. If necessary, interpolate soil temperatures and thermal inertias
244! -------------------------------------------------------------------
245      if (olddepthdef) then
246      ! tsoil needs to be interpolated, but not therm_i
247        allocate(oldgrid(dimlen+1))
248        allocate(oldval(dimlen+1))
249        allocate(newval(nsoil))
250
251        do ig=1,ngrid
252          ! copy values
253          oldval(1)=tsurf(ig)
254          oldval(2:dimlen+1)=oldtsoil(ig,1:dimlen)
255          ! build vertical coordinate
256          oldgrid(1)=0. ! ground
257          oldgrid(2:dimlen+1)=oldmlayer(1:dimlen)*
258     &                (inertiedat(ig,1)/volcapa)
259          ! interpolate
260          call interp_line(oldgrid,oldval,dimlen+1,mlayer,newval,nsoil)
261          ! copy result in tsoil
262          tsoil(ig,:)=newval(:)
263        enddo
264
265        ! cleanup
266        deallocate(oldgrid)
267        deallocate(oldval)
268        deallocate(newval)
269        interpol=.false. ! no need for interpolation any more     
270      endif !of if (olddepthdef)
271
272      if (interpol) then
273      write(*,*)'soil_settings: Vertical interpolation along new grid'
274      ! interpolate soil temperatures and thermal inertias
275        if (.not.allocated(oldgrid)) then
276          allocate(oldgrid(dimlen+1))
277          allocate(oldval(dimlen+1))
278          allocate(newval(nsoil))
279        endif
280
281      ! thermal inertia
282        do ig=1,ngrid
283          ! copy data
284          oldval(1:dimlen)=oldinertiedat(ig,dimlen)
285          ! interpolate
286          call interp_line(oldmlayer,oldval,dimlen,mlayer,newval,nsoil)
287          !copy result in inertiedat
288          inertiedat(ig,:)=newval(:)
289        enddo
290       
291      ! soil temperature
292        ! vertical coordinate
293        oldgrid(1)=0.0
294        oldgrid(2:dimlen+1)=oldmlayer(1:dimlen)
295        do ig=1,ngrid
296          ! data
297          oldval(1)=tsurf(ig)
298          oldval(2:dimlen+1)=oldtsoil(ig,1:dimlen)
299          ! interpolate
300          call interp_line(oldgrid,oldval,dimlen+1,mlayer,newval,nsoil)
301          ! copy result in inertiedat
302          tsoil(ig,:)=newval(:)
303        enddo
304       
305        !cleanup
306        deallocate(oldgrid)
307        deallocate(oldval)
308        deallocate(newval)
309        deallocate(oldinertiedat)
310        deallocate(oldtsoil)
311      endif ! of if (interpol)
312     
313! 6. Report min and max values of soil temperatures and thermal inertias
314! ----------------------------------------------------------------------
315
316      write(*,*)
317      write(*,*)'Soil volumetric heat capacity:',volcapa
318
319      xmin = MINVAL(inertiedat)
320      xmax = MAXVAL(inertiedat)
321      write(*,*)'Soil thermal inertia <inertiedat>:',xmin,xmax
322
323      xmin = 1.0E+20
324      xmax = -1.0E+20
325      xmin = MINVAL(tsoil)
326      xmax = MAXVAL(tsoil)
327      write(*,*)'Soil temperature <tsoil>:',xmin,xmax
328      end
Note: See TracBrowser for help on using the repository browser.