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

Last change on this file since 3608 was 3262, checked in by llange, 11 months ago

Mars PCM
reverting the revert commit -r3260. I've commited the wrong trunk. Sorry.
The bug with the soil index is fixed.
LL

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      IMPLICIT NONE
31      include "callkeys.h"
32!=======================================================================
33!   Description :
34!       Surface water ice / pore filling ice thermal inertia feedback.
35!
36!   When surface water-ice is thick enough (flag surfaceice_tifeedback), this routine creates a new
37!   soil thermal inertia with three different layers :
38!   - One layer of surface water ice (the thickness is given
39!     by the variable icecover (in kg of ice per m2) and the thermal
40!     inertia is prescribed by inert_h2o_ice (see surfdat_h));
41!   - A transitional layer of mixed thermal inertia;
42!   - A last layer of regolith below the ice cover whose thermal inertia
43!     is equal to inertiedat.
44!
45!   To use the model :
46!       SET THE surfaceice_tifeedback LOGICAL TO ".true." in callphys.def.
47!
48!   When pore filling ice is present, surface ice is computed as in Siegler et al., 2012
49!   \sqrt(surf_thermalinertia**2 + porosity*pore_filling*inertie_purewaterice**2)
50!
51!   For now, the code can not run with both options
52!
53!
54!   Author: J.-B. Madeleine Mars 2008 - Updated November 2012; Added porous ice by LL February 2024
55!=======================================================================
56
57! Local variables
58! ---------------
59
60      INTEGER :: ig                       ! Grid point (ngrid)
61      INTEGER :: islope                   ! SubGrid point (nslope)
62      INTEGER :: ik                       ! Grid point (nsoil)
63      INTEGER :: iref                     ! Ice/Regolith boundary index
64      REAL :: icedepth                    ! Ice cover thickness (m)
65      REAL :: inertie_purewaterice = 2100 ! Thermal inertia of pure water ice (J/m^2/K/s^1/2)
66
67! Inputs
68! ------
69      INTEGER :: ngrid                 ! Number of horizontal grid points
70      INTEGER :: nsoil                 ! Number of soil layers
71      INTEGER :: nslope                ! Number of subgrid slopes
72      REAL icecover(ngrid,nslope)      ! water iceon the surface (kg.m-2)
73      REAL poreice(ngrid,nsoil,nslope) ! pore ice filling fraction (1)
74! Outputs
75! -------
76
77      REAL newtherm_i(ngrid,nsoil,nslope)  ! New soil thermal inertia
78
79! Initialization
80! --------------
81
82  newtherm_i(1:ngrid,1:nsoil,1:nslope) = 0
83 
84  IF (surfaceice_tifeedback) THEN
85     
86! Creating the new soil thermal inertia table because of the massive surface ice
87! ------------------------------------------------------------------------------
88     DO islope = 1,nslope
89        DO ig=1,ngrid
90!       Calculating the ice cover thickness
91           icedepth=icecover(ig,islope)/rho_ice
92!       If the ice cover is too thick or watercaptag=true,
93!       the entire column is changed :
94           IF ((icedepth.ge.layer(nsoil)).or.(watercaptag(ig))) THEN
95              DO ik=1,nsoil
96                 newtherm_i(ig,ik,islope)=inert_h2o_ice
97              ENDDO
98!          We neglect the effect of a very thin ice cover :
99           ELSE IF (icedepth.lt.layer(1)) THEN
100              DO ik=1,nsoil
101                 newtherm_i(ig,ik,islope)=inertiedat(ig,ik)
102              ENDDO
103           ELSE
104!          Ice/regolith boundary index :
105              iref=1
106!          Otherwise, we find the ice/regolith boundary:
107              DO ik=1,nsoil-1
108                 IF ((icedepth.ge.layer(ik)).and.icedepth.lt.layer(ik+1)) THEN
109                    iref=ik+1
110                 EXIT
111                 ENDIF
112              ENDDO
113!             And we change the thermal inertia:
114              DO ik=1,iref-1
115                 newtherm_i(ig,ik,islope)=inert_h2o_ice
116              ENDDO
117!             Transition (based on the equations of thermal conduction):
118              newtherm_i(ig,iref,islope)=sqrt( (layer(iref)-layer(iref-1))/(((icedepth-layer(iref-1))/inert_h2o_ice**2) + &
119              ((layer(iref)-icedepth)/inertiedat(ig,ik)**2) ) )
120!              Underlying regolith:
121              DO ik=iref+1,nsoil
122                 newtherm_i(ig,ik,islope)=inertiedat(ig,ik)
123              ENDDO
124           ENDIF ! icedepth
125        ENDDO ! ig
126     ENDDO ! islope
127     
128  ELSE IF (poreice_tifeedback) THEN
129 
130! Updating soil thermal properties to includes the effect of porous ice
131! ------------------------------------------------------------------------------
132     DO islope = 1,nslope
133        newtherm_i(:,:,islope) = sqrt(inertiedat(:,:)**2 + porosity_reg*poreice(:,:,islope)*inertie_purewaterice**2)
134     ENDDO
135  ENDIF
136
137!=======================================================================
138
139END SUBROUTINE waterice_tifeedback
140END MODULE waterice_tifeedback_mod
Note: See TracBrowser for help on using the repository browser.