source: trunk/LMDZ.COMMON/libf/evolution/soil_TIfeedback_PEM.F90 @ 2849

Last change on this file since 2849 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: 3.4 KB
Line 
1      SUBROUTINE soil_TIfeedback_PEM(ngrid,nsoil,icecover,   newtherm_i)
2
3      use comsoil_h_PEM, only: layer_PEM, inertiedat_PEM
4
5      IMPLICIT NONE
6
7!=======================================================================
8!   Description :
9!       Surface water ice / Thermal inertia feedback.
10!
11!   When surface water-ice is thick enough, this routine creates a new
12!   soil thermal inertia with three different layers :
13!   - One layer of surface water ice (the thickness is given
14!     by the variable icecover (in kg of ice per m2) and the thermal
15!     inertia is prescribed by inert_h2o_ice (see surfdat_h));
16!   - A transitional layer of mixed thermal inertia;
17!   - A last layer of regolith below the ice cover whose thermal inertia
18!     is equal to inertiedat.
19!
20!  To use the model :
21!      SET THE tifeedback LOGICAL TO ".true." in callphys.def.
22!
23!  Author: Adapted from J.-B. Madeleine Mars 2008 ( Updated November 2012) by LL, 2022
24!=======================================================================
25
26!Local variables
27!---------------
28
29      INTEGER :: ig                     ! Grid point (ngrid)
30      INTEGER :: ik                     ! Grid point (nsoil)
31      INTEGER :: iref                   ! Ice/Regolith boundary index
32      INTEGER, INTENT(IN) :: ngrid                  ! Number of horizontal grid points
33      INTEGER, INTENT(IN) :: nsoil                  ! Number of soil layers
34      REAL :: icedepth                  ! Ice cover thickness (m)
35      REAL :: inert_h2o_ice = 800.
36      REAL :: rho_ice = 920.
37      REAL :: prev_thermi(ngrid,nsoil)
38!Inputs
39!------
40
41      REAL ,INTENT(IN):: icecover(ngrid)         ! tracer on the surface (kg.m-2)
42
43!Outputs
44!-------
45
46      REAL,INTENT(INOUT) :: newtherm_i(ngrid,nsoil)    ! New soil thermal inertia
47
48      prev_thermi(:,:) = newtherm_i(:,:)
49
50!Creating the new soil thermal inertia table
51!-------------------------------------------
52      DO ig=1,ngrid
53!      Calculating the ice cover thickness
54       
55        icedepth=icecover(ig)/rho_ice
56       
57!      If the ice cover is too thick or watercaptag=true,
58!        the entire column is changed :
59        IF (icedepth.ge.layer_PEM(nsoil)) THEN
60          DO ik=1,nsoil
61               newtherm_i(ig,ik)=max(inert_h2o_ice,prev_thermi(ig,ik))
62          ENDDO
63!      We neglect the effect of a very thin ice cover :
64        ELSE IF (icedepth.lt.layer_PEM(1)) THEN
65          DO ik=1,nsoil
66               newtherm_i(ig,ik)=inertiedat_PEM(ig,ik)
67          ENDDO
68        ELSE
69!        Ice/regolith boundary index :
70          iref=1
71!        Otherwise, we find the ice/regolith boundary:
72          DO ik=1,nsoil-1
73              IF ((icedepth.ge.layer_PEM(ik)).and. (icedepth.lt.layer_PEM(ik+1))) THEN
74                  iref=ik+1
75                  EXIT
76              ENDIF
77          ENDDO
78!        And we change the thermal inertia:
79          DO ik=1,iref-1
80            newtherm_i(ig,ik)=max(inert_h2o_ice,prev_thermi(ig,ik))
81          ENDDO
82!        Transition (based on the equations of thermal conduction):
83          newtherm_i(ig,iref)=sqrt( (layer_PEM(iref)-layer_PEM(iref-1)) / &
84           ( ((icedepth-layer_PEM(iref-1))/newtherm_i(ig,iref-1)**2) + &
85             ((layer_PEM(iref)-icedepth)/inertiedat_PEM(ig,ik)**2) ) )
86!        Underlying regolith:
87          DO ik=iref+1,nsoil
88              newtherm_i(ig,ik)=inertiedat_PEM(ig,ik)
89          ENDDO
90        ENDIF ! icedepth
91      ENDDO ! ig
92
93!=======================================================================
94      RETURN
95      END
Note: See TracBrowser for help on using the repository browser.