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

Last change on this file since 2950 was 2945, checked in by llange, 3 years ago

PEM
Modification in recomp_tend_co2_slope. The emissivity of ice was assumed to be 0.95, but it can be lower. It is now set to the values given by the PCM
Remove unused variables (n_1km)

LL

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