Ignore:
Timestamp:
Dec 4, 2024, 4:04:54 PM (7 months ago)
Author:
jbclement
Message:

PEM:
Removing unecessary module/subroutine "interpol_TI_PEM2PCM.F90" + Few small corrections/cleanings.
JBC

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/compute_soiltemp_mod.F90

    r3525 r3532  
    44!-----------------------------------------------------------------------
    55!  Author: LL
    6 !  Purpose: This module gathers the different routines used in the PEM to compute the soil temperature evolution and initialisation. 
    7 ! 
    8 !  Note: depths of layers and mid-layers, soil thermal inertia and 
     6!  Purpose: This module gathers the different routines used in the PEM to compute the soil temperature evolution and initialisation.
     7!
     8!  Note: depths of layers and mid-layers, soil thermal inertia and
    99!        heat capacity are commons in comsoil_PEM.h
    1010!-----------------------------------------------------------------------
     
    1212!=======================================================================
    1313
    14 
    15 
    1614SUBROUTINE compute_tsoil_pem(ngrid,nsoil,firstcall,therm_i,timestep,tsurf,tsoil)
    1715
     
    2422!  Author: LL
    2523!  Purpose: Compute soil temperature using an implict 1st order scheme
    26 ! 
    27 !  Note: depths of layers and mid-layers, soil thermal inertia and 
     24!
     25!  Note: depths of layers and mid-layers, soil thermal inertia and
    2826!        heat capacity are commons in comsoil_PEM.h
    2927!-----------------------------------------------------------------------
     
    3129#include "dimensions.h"
    3230
    33 !-----------------------------------------------------------------------
    34 !  arguments
    35 !  ---------
    36 !  inputs:
    37 integer,                      intent(in) :: ngrid     ! number of (horizontal) grid-points
    38 integer,                      intent(in) :: nsoil     ! number of soil layers 
    39 logical,                      intent(in) :: firstcall ! identifier for initialization call
     31! Inputs:
     32! -------
     33integer,                      intent(in) :: ngrid     ! number of (horizontal) grid-points
     34integer,                      intent(in) :: nsoil     ! number of soil layers
     35logical,                      intent(in) :: firstcall ! identifier for initialization call
    4036real, dimension(ngrid,nsoil), intent(in) :: therm_i   ! thermal inertia [SI]
    4137real,                         intent(in) :: timestep  ! time step [s]
    4238real, dimension(ngrid),       intent(in) :: tsurf     ! surface temperature [K]
    43  
    44 ! outputs:
     39! Outputs:
     40!---------
    4541real, dimension(ngrid,nsoil), intent(inout) :: tsoil ! soil (mid-layer) temperature [K]
    46 ! local variables:
    47 integer :: ig, ik   
     42! Local:
     43!-------
     44integer :: ig, ik
    4845
    4946! 0. Initialisations and preprocessing step
     
    5249    do ig = 1,ngrid
    5350        do ik = 0,nsoil - 1
    54             mthermdiff_PEM(ig,ik) = therm_i(ig,ik + 1)*therm_i(ig,ik + 1)/volcapa   
     51            mthermdiff_PEM(ig,ik) = therm_i(ig,ik + 1)*therm_i(ig,ik + 1)/volcapa
    5552        enddo
    5653    enddo
     
    6461    enddo
    6562
    66 ! 0.3 Build coefficients mu_PEM, q_{k+1/2}, d_k, alph_PEMa_k and capcal
     63! 0.3 Build coefficients mu_PEM, q_{k+1/2}, d_k, alph_PEM
    6764    ! mu_PEM
    6865    mu_PEM = mlayer_PEM(0)/(mlayer_PEM(1) - mlayer_PEM(0))
     
    9996! Other layers:
    10097        do ik = 1,nsoil - 1
    101                 tsoil(ig,ik + 1) = alph_PEM(ig,ik)*tsoil(ig,ik) + beta_PEM(ig,ik) 
     98                tsoil(ig,ik + 1) = alph_PEM(ig,ik)*tsoil(ig,ik) + beta_PEM(ig,ik)
    10299        enddo
    103100    enddo
     
    139136#include "dimensions.h"
    140137
    141 !-----------------------------------------------------------------------
    142 !  arguments
    143 !  ---------
    144 !  inputs:
     138! Inputs:
     139!--------
    145140integer,                      intent(in) :: ngrid   ! number of (horizontal) grid-points
    146141integer,                      intent(in) :: nsoil   ! number of soil layers
    147142real, dimension(ngrid,nsoil), intent(in) :: therm_i ! thermal inertia [SI]
    148143real, dimension(ngrid),       intent(in) :: tsurf   ! surface temperature [K]
    149 
    150 ! outputs:
     144! Outputs:
     145!---------
    151146real, dimension(ngrid,nsoil), intent(inout) :: tsoil ! soil (mid-layer) temperature [K]
    152 ! local variables:
     147! Local:
     148!-------
    153149integer :: ig, ik, iloop
    154150
     
    169165enddo
    170166
    171 ! 0.3 Build coefficients mu_PEM, q_{k+1/2}, d_k, alph_PEMa_k and capcal
     167! 0.3 Build coefficients mu_PEM, q_{k+1/2}, d_k, alph_PEM
    172168! mu_PEM
    173169mu_PEM = mlayer_PEM(0)/(mlayer_PEM(1) - mlayer_PEM(0))
     
    179175do ig = 1,ngrid
    180176    ! d_k
    181     do ik = 1,nsoil-1
     177    do ik = 1,nsoil - 1
    182178        coefd_PEM(ig,ik) = thermdiff_PEM(ig,ik)/(mlayer_PEM(ik) - mlayer_PEM(ik - 1))
    183179    enddo
     
    207203!  2. Compute soil temperatures
    208204do iloop = 1,10 !just convergence
    209     ! First layer:
    210     do ig = 1,ngrid
    211         tsoil(ig,1)=(tsurf(ig) + mu_PEM*beta_PEM(ig,1)*thermdiff_PEM(ig,1)/mthermdiff_PEM(ig,0))/ &
    212                    (1. + mu_PEM*(1. - alph_PEM(ig,1))*thermdiff_PEM(ig,1)/mthermdiff_PEM(ig,0))
    213     ! Other layers:
    214     do ik = 1,nsoil - 1
    215         tsoil(ig,ik + 1) = alph_PEM(ig,ik)*tsoil(ig,ik) + beta_PEM(ig,ik)
    216     enddo
    217 enddo
    218 
     205    do ig = 1,ngrid
     206        ! First layer:
     207        tsoil(ig,1) = (tsurf(ig) + mu_PEM*beta_PEM(ig,1)*thermdiff_PEM(ig,1)/mthermdiff_PEM(ig,0))/ &
     208                      (1. + mu_PEM*(1. - alph_PEM(ig,1))*thermdiff_PEM(ig,1)/mthermdiff_PEM(ig,0))
     209        ! Other layers:
     210        do ik = 1,nsoil - 1
     211            tsoil(ig,ik + 1) = alph_PEM(ig,ik)*tsoil(ig,ik) + beta_PEM(ig,ik)
     212        enddo
     213    enddo
    219214enddo ! iloop
    220215
Note: See TracChangeset for help on using the changeset viewer.