source: trunk/LMDZ.MARS/libf/phymars/waterice_tifeedback_mod.F90 @ 3807

Last change on this file since 3807 was 3726, checked in by emillour, 2 months ago

Mars PCM:
Turn "callkeys.h" into module "callkeys_mod.F90"
EM

File size: 5.8 KB
Line 
1MODULE waterice_tifeedback_mod
2 
3!======================================================================================================================!
4! Subject:
5!---------
6!   Module used to compute the thermal inertia of an icy soil (either pore filling or massive ice)
7!----------------------------------------------------------------------------------------------------------------------!
8! Reference:
9!-----------
10!  For pure ice on the surface: J.-B. Madeleine, F. Forget, James W. Head, B. Levrard, F. Montmessin, E. Millour,
11!  Amazonian northern mid-latitude glaciation on Mars: A proposed climate scenario, Icarus (10.1016/j.icarus.2009.04.037).
12!
13!  For pore-filling ice: Siegler, M., O. Aharonson, E. Carey, M. Choukroun, T. Hudson, N. Schorghofer, and S. Xu (2012), Measurements of thermal properties of icy Mars regolith analogs, JGR (10.1029/2011JE003938).
14!
15! Originally written by JBM for pure ice (2008-2012), moved in to a module and .F90 by LL (2024). Pore filling ice included by LL (2024)
16!
17!======================================================================================================================!
18
19
20
21IMPLICIT NONE
22
23CONTAINS
24
25SUBROUTINE waterice_tifeedback(ngrid,nsoil,nslope,icecover,poreice,newtherm_i)
26
27      use tracer_mod, only: rho_ice
28      use comsoil_h, only: layer, inertiedat, porosity_reg
29      use surfdat_h, only: watercaptag, inert_h2o_ice
30      use callkeys_mod, only: poreice_tifeedback, surfaceice_tifeedback
31      IMPLICIT NONE
32
33!=======================================================================
34!   Description :
35!       Surface water ice / pore filling ice thermal inertia feedback.
36!
37!   When surface water-ice is thick enough (flag surfaceice_tifeedback), this routine creates a new
38!   soil thermal inertia with three different layers :
39!   - One layer of surface water ice (the thickness is given
40!     by the variable icecover (in kg of ice per m2) and the thermal
41!     inertia is prescribed by inert_h2o_ice (see surfdat_h));
42!   - A transitional layer of mixed thermal inertia;
43!   - A last layer of regolith below the ice cover whose thermal inertia
44!     is equal to inertiedat.
45!
46!   To use the model :
47!       SET THE surfaceice_tifeedback LOGICAL TO ".true." in callphys.def.
48!
49!   When pore filling ice is present, surface ice is computed as in Siegler et al., 2012
50!   \sqrt(surf_thermalinertia**2 + porosity*pore_filling*inertie_purewaterice**2)
51!
52!   For now, the code can not run with both options
53!
54!
55!   Author: J.-B. Madeleine Mars 2008 - Updated November 2012; Added porous ice by LL February 2024
56!=======================================================================
57
58! Local variables
59! ---------------
60
61      INTEGER :: ig                       ! Grid point (ngrid)
62      INTEGER :: islope                   ! SubGrid point (nslope)
63      INTEGER :: ik                       ! Grid point (nsoil)
64      INTEGER :: iref                     ! Ice/Regolith boundary index
65      REAL :: icedepth                    ! Ice cover thickness (m)
66      REAL :: inertie_purewaterice = 2100 ! Thermal inertia of pure water ice (J/m^2/K/s^1/2)
67
68! Inputs
69! ------
70      INTEGER :: ngrid                 ! Number of horizontal grid points
71      INTEGER :: nsoil                 ! Number of soil layers
72      INTEGER :: nslope                ! Number of subgrid slopes
73      REAL icecover(ngrid,nslope)      ! water iceon the surface (kg.m-2)
74      REAL poreice(ngrid,nsoil,nslope) ! pore ice filling fraction (1)
75! Outputs
76! -------
77
78      REAL newtherm_i(ngrid,nsoil,nslope)  ! New soil thermal inertia
79
80! Initialization
81! --------------
82
83  newtherm_i(1:ngrid,1:nsoil,1:nslope) = 0
84 
85  IF (surfaceice_tifeedback) THEN
86     
87! Creating the new soil thermal inertia table because of the massive surface ice
88! ------------------------------------------------------------------------------
89     DO islope = 1,nslope
90        DO ig=1,ngrid
91!       Calculating the ice cover thickness
92           icedepth=icecover(ig,islope)/rho_ice
93!       If the ice cover is too thick or watercaptag=true,
94!       the entire column is changed :
95           IF ((icedepth.ge.layer(nsoil)).or.(watercaptag(ig))) THEN
96              DO ik=1,nsoil
97                 newtherm_i(ig,ik,islope)=inert_h2o_ice
98              ENDDO
99!          We neglect the effect of a very thin ice cover :
100           ELSE IF (icedepth.lt.layer(1)) THEN
101              DO ik=1,nsoil
102                 newtherm_i(ig,ik,islope)=inertiedat(ig,ik)
103              ENDDO
104           ELSE
105!          Ice/regolith boundary index :
106              iref=1
107!          Otherwise, we find the ice/regolith boundary:
108              DO ik=1,nsoil-1
109                 IF ((icedepth.ge.layer(ik)).and.icedepth.lt.layer(ik+1)) THEN
110                    iref=ik+1
111                 EXIT
112                 ENDIF
113              ENDDO
114!             And we change the thermal inertia:
115              DO ik=1,iref-1
116                 newtherm_i(ig,ik,islope)=inert_h2o_ice
117              ENDDO
118!             Transition (based on the equations of thermal conduction):
119              newtherm_i(ig,iref,islope)=sqrt( (layer(iref)-layer(iref-1))/(((icedepth-layer(iref-1))/inert_h2o_ice**2) + &
120              ((layer(iref)-icedepth)/inertiedat(ig,ik)**2) ) )
121!              Underlying regolith:
122              DO ik=iref+1,nsoil
123                 newtherm_i(ig,ik,islope)=inertiedat(ig,ik)
124              ENDDO
125           ENDIF ! icedepth
126        ENDDO ! ig
127     ENDDO ! islope
128     
129  ELSE IF (poreice_tifeedback) THEN
130 
131! Updating soil thermal properties to includes the effect of porous ice
132! ------------------------------------------------------------------------------
133     DO islope = 1,nslope
134        newtherm_i(:,:,islope) = sqrt(inertiedat(:,:)**2 + porosity_reg*poreice(:,:,islope)*inertie_purewaterice**2)
135     ENDDO
136  ENDIF
137
138!=======================================================================
139
140END SUBROUTINE waterice_tifeedback
141END MODULE waterice_tifeedback_mod
Note: See TracBrowser for help on using the repository browser.