source: trunk/LMDZ.COMMON/libf/evolution/update_soil.F90 @ 2909

Last change on this file since 2909 was 2895, checked in by llange, 2 years ago

PEM
Soil temperature initialisation has been updated
Conf_PEM improved by adding some options to the users (thermal regolith depend on the pressure, depth of the subsurface layers, etc.)
Minor edits then (+ svn update with RV had some issues, so there are some "artefact changes" ...)
LL

File size: 5.2 KB
RevLine 
[2895]1   SUBROUTINE update_soil(ngrid,nslope,nsoil_PEM,tendencies_waterice,waterice,p_avg_new,ice_depth,TI_PEM)
[2842]2#ifndef CPP_STD
[2794]3 USE comsoil_h, only:  inertiedat, volcapa
[2895]4 USE comsoil_h_PEM, only: layer_PEM,n_1km,inertiedat_PEM,depth_breccia,depth_bedrock,index_breccia,index_bedrock,reg_thprop_dependp
[2794]5 USE vertical_layers_mod, ONLY: ap,bp
[2863]6 USE comsoil_h_PEM, only: n_1km
[2794]7 implicit none
8! Input:
[2895]9 INTEGER,INTENT(IN) ::  ngrid, nslope, nsoil_PEM
[2835]10 REAL,INTENT(IN) :: p_avg_new
[2888]11 REAL,INTENT(IN) :: tendencies_waterice(ngrid,nslope)
[2794]12 REAL,INTENT(IN) :: waterice(ngrid,nslope)
13 REAL,INTENT(in) :: ice_depth(ngrid,nslope)
14! Outputs:
15
16 REAL,INTENT(INOUT) :: TI_PEM(ngrid,nsoil_PEM,nslope)
17 
18! Constants:
19
20 REAL ::  inertie_thresold = 800. ! look for ice
21 REAL ::  inertie_averaged = 250 ! Mellon et al. 2000
[2849]22 REAL ::  ice_inertia = 1200  ! Inertia of ice
[2888]23 REAL ::  P610 = 610.0       ! current average pressure on Mars [Pa]
24 REAL :: TI_breccia = 750.   ! THermal inertia of Breccia following Wood 2009 [SI]
25 REAL :: TI_bedrock = 2300.  ! Thermal inertia of Bedrock following Wood 2009 [SI]
[2794]26
27! Local variables:
28
29 INTEGER :: ig,islope,iloop,iref,k
30 REAL :: regolith_inertia(ngrid,nslope) ! TI of the regolith
[2888]31 REAL :: delta
32 REAL :: TI_breccia_new
33!  1.Ice TI feedback
[2794]34
[2849]35!    do islope = 1,nslope
[2888]36!     call soil_TIfeedback_PEM(ngrid,nsoil_PEM,waterice(:,islope),   TI_PEM(:,:,islope))
[2849]37!    enddo
[2794]38
[2888]39! 2. Modification of the regolith thermal inertia.
[2794]40
41
42
[2888]43 do islope = 1,nslope
44   regolith_inertia(:,islope) = inertiedat_PEM(:,1)
45   do ig = 1,ngrid
46      if((tendencies_waterice(ig,islope).lt.-1e-5).and.(waterice(ig,islope).eq.0)) then
47              regolith_inertia(ig,islope) = inertie_averaged
48       endif
[2895]49      if(reg_thprop_dependp) then
50          if(TI_PEM(ig,1,islope).lt.inertie_thresold) then
51            regolith_inertia(ig,islope) = regolith_inertia(ig,islope)*(p_avg_new/P610)**0.3
52          endif
53         TI_breccia_new = TI_breccia*(p_avg_new/P610)**0.3
54      else
55         TI_breccia_new = TI_breccia
56      endif
[2888]57   enddo
58 enddo
[2794]59
[2888]60
61! 3. Build new Thermal Inertia
62
63do  islope=1,nslope
64   do ig = 1,ngrid
[2895]65     do iloop = 1,index_breccia
[2888]66         TI_PEM(ig,iloop,islope) = regolith_inertia(ig,islope)
67     enddo
68     if(regolith_inertia(ig,islope).lt.TI_breccia_new) then
69!!! transition
[2895]70             delta = depth_breccia
71             TI_PEM(ig,index_breccia+1,islope) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ &
72            (((delta-layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2))+ &
73                      ((layer_PEM(index_breccia+1)-delta)/(TI_breccia_new**2))))
74            do iloop=index_breccia+2,index_bedrock
[2888]75              TI_PEM(ig,iloop,islope) = TI_breccia_new
76            enddo     
77      else ! we keep the high ti values
[2895]78            do iloop=index_breccia+1,index_bedrock
79              TI_PEM(ig,iloop,islope) = TI_PEM(ig,index_breccia,islope)
[2888]80            enddo
81       endif ! TI PEM and breccia comparison
82!! transition
[2895]83       delta = depth_bedrock
84       TI_PEM(ig,index_bedrock+1,islope) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ &
85            (((delta-layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2))+ &
86            ((layer_PEM(index_bedrock+1)-delta)/(TI_bedrock**2))))
87       do iloop=index_bedrock+2,nsoil_PEM
[2888]88            TI_PEM(ig,iloop,islope) = TI_bedrock
89       enddo   
90      enddo ! ig
91ENDDO ! islope
92
93!  4. Build new TI in case of ice table
[2794]94! a) For the regolith
95  do ig=1,ngrid
96    do islope=1,nslope
[2895]97!      do iloop = 1,index_bedrock
98!       TI_PEM(ig,iloop,islope) = TI_PEM(ig,1,islope)
99!      enddo
[2794]100  if (ice_depth(ig,islope).gt. -1.e-10) then
101! 3.0 FIrst if permanent ice
102   if (ice_depth(ig,islope).lt. 1e-10) then
103      do iloop = 1,nsoil_PEM
[2895]104       TI_PEM(ig,iloop,islope)=ice_inertia
[2794]105      enddo
106     else
107      ! 4.1 find the index of the mixed layer
108      iref=0 ! initialize iref
109      do k=1,nsoil_PEM ! loop on layers
110        if (ice_depth(ig,islope).ge.layer_PEM(k)) then
111          iref=k ! pure regolith layer up to here
112        else
113         ! correct iref was obtained in previous cycle
114         exit
115        endif
116      enddo
117
118      ! 4.2 Build the new ti
119      do iloop=1,iref
[2863]120         TI_PEM(ig,iloop,islope) =TI_PEM(ig,1,islope)
[2794]121      enddo
122      if (iref.lt.nsoil_PEM) then
123        if (iref.ne.0) then
124          ! mixed layer
125           TI_PEM(ig,iref+1,islope)=sqrt((layer_PEM(iref+1)-layer_PEM(iref))/ &
126            (((ice_depth(ig,islope)-layer_PEM(iref))/(TI_PEM(ig,iref,islope)**2))+ &
127                      ((layer_PEM(iref+1)-ice_depth(ig,islope))/(ice_inertia**2))))
128        else ! first layer is already a mixed layer
129          ! (ie: take layer(iref=0)=0)
130          TI_PEM(ig,1,islope)=sqrt((layer_PEM(1))/ &
131                          (((ice_depth(ig,islope))/(TI_PEM(ig,1,islope)**2))+ &
132                           ((layer_PEM(1)-ice_depth(ig,islope))/(ice_inertia**2))))
133        endif ! of if (iref.ne.0)       
134        ! lower layers of pure ice
135        do iloop=iref+2,nsoil_PEM
136          TI_PEM(ig,iloop,islope)=ice_inertia
137        enddo
138      endif ! of if (iref.lt.(nsoilmx))
139      endif ! permanent glaciers
140      endif ! depth > 0
141     enddo !islope
142    enddo !ig
143
144!=======================================================================
145      RETURN
[2842]146#endif
[2794]147      END
Note: See TracBrowser for help on using the repository browser.