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

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

PEM
H2O adsorption is now computed. Total mass of H2o adsorbded is written in the restart_PEM.
+Minor fixes and edit
LL & RV

File size: 4.5 KB
Line 
1   SUBROUTINE update_soil(ngrid,nslope,nsoil_PEM,tend_h2oglaciers,tend_co2glaciers,co2ice,waterice,p_avg_new,&
2                          ice_depth,TI_PEM)
3#ifndef CPP_STD
4 USE comsoil_h, only:  inertiedat, volcapa
5 USE comsoil_h_PEM, only: layer_PEM,n_1km,inertiedat_PEM
6 USE vertical_layers_mod, ONLY: ap,bp
7 USE comsoil_h_PEM, only: n_1km
8 implicit none
9! Input:
10 INTEGER,INTENT(IN) ::  ngrid, nslope, nsoil_PEM
11 REAL,INTENT(IN) :: tend_h2oglaciers(ngrid,nslope),tend_co2glaciers(ngrid,nslope)
12 REAL,INTENT(IN) :: p_avg_new
13 REAL,INTENT(IN) :: co2ice(ngrid,nslope)
14 REAL,INTENT(IN) :: waterice(ngrid,nslope)
15 REAL,INTENT(in) :: ice_depth(ngrid,nslope)
16
17! Outputs:
18
19 REAL,INTENT(INOUT) :: TI_PEM(ngrid,nsoil_PEM,nslope)
20 
21! Constants:
22
23 REAL ::  alpha = 0.2
24 REAL ::  beta = 1.08e7
25 REAL ::  To = 273.15
26 REAL ::  R =  8.314
27 REAL ::  L =  51058.
28 REAL ::  inertie_thresold = 800. ! look for ice
29 REAL ::  inertie_averaged = 250 ! Mellon et al. 2000
30 REAL ::  ice_inertia = 1200  ! Inertia of ice
31 REAL ::  P610 = 610.0
32 REAL ::  m_h2o = 18.01528E-3
33 REAL ::  m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)   
34 REAL ::  m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)   
35 REAL ::  A,B,mmean             
36
37! Local variables:
38
39 INTEGER :: ig,islope,iloop,iref,k
40 REAL :: regolith_inertia(ngrid,nslope) ! TI of the regolith
41 REAL :: d(ngrid,nsoil_PEM,nslope)
42 REAL :: Total_surface
43 INTEGER :: ispermanent_co2glaciers(ngrid,nslope)
44 INTEGER :: ispermanent_h2oglaciers(ngrid,nslope)
45
46! 0. Initialisation
47
48!  do ig = 1,ngrid
49!    do islope = 1,nslope
50!     if((abs(tend_h2oglaciers(ig,islope)).lt.1e-5).and.(abs(waterice(ig,islope)).gt.(1.e-4))) then
51!        ispermanent_h2oglaciers(ig,islope) = 1
52!     else
53!        ispermanent_h2oglaciers(ig,islope) = 0
54!     endif
55!
56!     if((abs(tend_co2glaciers(ig,islope)).lt.1e-5).and.(abs(co2ice(ig,islope)).gt.(1.e-4))) then
57!        ispermanent_co2glaciers(ig,islope) = 1
58!     else
59!        ispermanent_co2glaciers(ig,islope) = 0
60!     endif
61!    enddo
62!  enddo
63
64
65
66!  1.Ice TI feedback
67
68!    do islope = 1,nslope
69!     call soil_TIfeedback_PEM(ngrid,nsoil_PEM,waterice(:,islope),   TI_PEM(:,:,islope))
70!    enddo
71
72! 2. Modification of the regolith thermal inertia.
73
74!  do ig=1,ngrid
75!    do islope=1,nslope
76!     do iloop =1,n_1km
77!       d(ig,iloop,islope) = ((inertiedat_PEM(ig,iloop)*inertiedat_PEM(ig,iloop))/(volcapa*alpha*P610**0.6))**(-1/(0.11*log10(P610/beta)))
78!   if(TI_PEM(ig,iloop,islope).lt.inertie_thresold) then !           we are modifying the regolith properties, not ice
79!          TI_PEM(ig,iloop,islope) = sqrt(volcapa*alpha*(p_avg_new**0.6)* d(ig,iloop,islope)**(-0.11*log10(p_avg_new/beta)))
80!
81!   endif
82!     enddo
83!   enddo
84!enddo
85
86!  3. Build new TI for the PEM
87! a) For the regolith
88  do ig=1,ngrid
89    do islope=1,nslope
90      do iloop = 1,n_1km
91       TI_PEM(ig,iloop,islope) = TI_PEM(ig,1,islope)
92      enddo
93  if (ice_depth(ig,islope).gt. -1.e-10) then
94! 3.0 FIrst if permanent ice
95   if (ice_depth(ig,islope).lt. 1e-10) then
96      do iloop = 1,nsoil_PEM
97       TI_PEM(ig,iloop,islope)=max(ice_inertia,inertiedat_PEM(ig,iloop))
98      enddo
99     else
100      ! 4.1 find the index of the mixed layer
101      iref=0 ! initialize iref
102      do k=1,nsoil_PEM ! loop on layers
103        if (ice_depth(ig,islope).ge.layer_PEM(k)) then
104          iref=k ! pure regolith layer up to here
105        else
106         ! correct iref was obtained in previous cycle
107         exit
108        endif
109      enddo
110
111      ! 4.2 Build the new ti
112      do iloop=1,iref
113         TI_PEM(ig,iloop,islope) =TI_PEM(ig,1,islope)
114      enddo
115      if (iref.lt.nsoil_PEM) then
116        if (iref.ne.0) then
117          ! mixed layer
118           TI_PEM(ig,iref+1,islope)=sqrt((layer_PEM(iref+1)-layer_PEM(iref))/ &
119            (((ice_depth(ig,islope)-layer_PEM(iref))/(TI_PEM(ig,iref,islope)**2))+ &
120                      ((layer_PEM(iref+1)-ice_depth(ig,islope))/(ice_inertia**2))))
121        else ! first layer is already a mixed layer
122          ! (ie: take layer(iref=0)=0)
123          TI_PEM(ig,1,islope)=sqrt((layer_PEM(1))/ &
124                          (((ice_depth(ig,islope))/(TI_PEM(ig,1,islope)**2))+ &
125                           ((layer_PEM(1)-ice_depth(ig,islope))/(ice_inertia**2))))
126        endif ! of if (iref.ne.0)       
127        ! lower layers of pure ice
128        do iloop=iref+2,nsoil_PEM
129          TI_PEM(ig,iloop,islope)=ice_inertia
130        enddo
131      endif ! of if (iref.lt.(nsoilmx))
132      endif ! permanent glaciers
133      endif ! depth > 0
134     enddo !islope
135    enddo !ig
136
137!=======================================================================
138      RETURN
139#endif
140      END
Note: See TracBrowser for help on using the repository browser.