source: trunk/LMDZ.GENERIC/libf/phystd/soil_settings.F @ 1520

Last change on this file since 1520 was 1516, checked in by emillour, 10 years ago

Generic model:

  • Added tests to ensure that soil model settings are adequate to resolve sub-surface diurnal and annual thermal waves.

EM

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