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

Last change on this file since 2794 was 2794, checked in by llange, 2 years ago

MARS PEM:

  • Add a PEMETAT0 that read "startfi_pem.nc"
  • Add the soil in the model: soil temperature, thermal properties, ice table
  • Add a routine that compute CO2 + H2O adsorption
  • Minor corrections in PEM.F90

LL

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