source: trunk/LMDZ.PLUTO/libf/phypluto/soil_settings.F90 @ 3503

Last change on this file since 3503 was 3503, checked in by afalco, 13 days ago

Pluto: surfini.F and soil_settings.F to .F90.
AF

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