source: trunk/LMDZ.MARS/libf/phymars/soil_tifeedback.F @ 834

Last change on this file since 834 was 834, checked in by jbmadeleine, 12 years ago

Mars GCM:
Added the file soil_tifeedback.F.

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