source: trunk/mars/libf/phymars/soil_settings.F @ 38

Last change on this file since 38 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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