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

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

PEM
Thermal Inertia is now only read in the start and not read in the xios
file
Fixing few bug (problem of allocation and index for update_soil and some
variables in the pem)
LL

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