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

Last change on this file since 2840 was 2835, checked in by romain.vande, 3 years ago

Mars PEM:
Introduction of the possibility to follow an orbital forcing.
Introduction of new control parameters.
Cleaning of the PEM (removing unused files, add comments and new files)

A file named run_PEM.def can be added to the run.def. It contains the following variables:

_ evol_orbit_pem: Boolean. Do you want to follow an orbital forcing predefined (read in ob_ex_lsp.asc for example)? (default=false)
_ year_bp_ini: Integer. Number of year before present to start the pem run if evol_orbit_pem=.true. , default=0
_ Max_iter_pem: Integer. Maximal number of iteration if none of the stopping criterion is reached and if evol_orbit_pem=.false., default=99999999
_ dt_pem: Integer. Time step of the PEM in year, default=1
_ alpha_criterion: Real. Acceptance rate of sublimating ice surface change, default=0.2
_ soil_pem: Boolean. Do you want to run with subsurface physical processes in the PEM? default=.true.

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