source: trunk/LMDZ.COMMON/libf/evolution/soil_TIfeedback_PEM_mod.F90 @ 3495

Last change on this file since 3495 was 3076, checked in by jbclement, 14 months ago

PEM:
Big cleaning/improvements of the PEM:

  • Conversion of "abort_pem.F" and "soil_settings_PEM.F" into Fortran 90;
  • Transformation of every PEM subroutines into module;
  • Rewriting of many subroutines with modern Fortran syntax;
  • Correction of a bug in "pem.F90" when calling 'recomp_tend_co2_slope'. The arguments were given in disorder and emissivity was missing;
  • Update of "launch_pem.sh" in deftank.

JBC

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