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

Last change on this file since 1036 was 1036, checked in by emillour, 11 years ago

Mars GCM: (a first step towards using parallel dynamics)

  • IMPORTANT CHANGE: Implemented dynamic tracers. It is no longer necessary to compile the model with the '-t #' option, number of tracers is simply read from tracer.def file (as before). Adapted makegcm_* scripts (and co.) accordingly. Technical aspects of the switch to dynamic tracers are:
    • advtrac.h (in dyn3d) removed and replaced by module infotrac.F
    • tracer.h (in phymars) removed and replaced by module tracer_mod.F90 (which contains nqmx, the number of tracers, etc. and can be used anywhere in the physics).
  • Included some side cleanups: removed unused files (in dyn3d) anldoppler2.F, anl_mcdstats.F and anl_stats-diag.F, and all the unecessary dimensions.* files in grid/dimension.
  • Checked that changes are clean and that GCM yields identical results (in debug mode) to previous svn version.

EM

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