Changeset 2539 for trunk/LMDZ.VENUS


Ignore:
Timestamp:
Jun 23, 2021, 5:55:48 PM (3 years ago)
Author:
emillour
Message:

Venus GCM:
Fix soil model so that it correctly computes soil temperatures at the first time step. And in the process make it 1+1=2 compliant.
VB+EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/soil.F

    r1530 r2539  
    4646c   -------------
    4747
    48       use dimphy
     48      use dimphy, only: klon
    4949      IMPLICIT NONE
    50 #include "YOMCST.h"
    51 #include "dimsoil.h"
    52 #include "clesphys.h"
     50      include "YOMCST.h"
     51      include "dimsoil.h"
     52      include "clesphys.h"
    5353
    5454c-----------------------------------------------------------------------
     
    5656c  ---------
    5757
    58       REAL ptimestep
    59       INTEGER knon
    60       REAL ptsrf(klon),ptsoil(klon,nsoilmx)
    61       REAL pcapcal(klon),pfluxgrd(klon)
     58      REAL, intent(IN) :: ptimestep
     59      INTEGER, intent(IN) :: knon
     60      REAL, intent(IN) :: ptsrf(klon)
     61      REAL, intent(OUT) :: ptsoil(klon,nsoilmx)
     62      REAL, intent(OUT) :: pcapcal(klon),pfluxgrd(klon)
    6263
    6364c-----------------------------------------------------------------------
     
    7273c   local saved variables:
    7374c   ----------------------
    74       REAL dz1(nsoilmx),dz2(nsoilmx)
    75       REAL,allocatable :: zc(:,:),zd(:,:)
    76       REAL lambda
    77       SAVE dz1,dz2,zc,zd,lambda
    78       LOGICAL firstcall
    79       SAVE firstcall
    80 
    81       DATA firstcall/.true./
    82 
    83 c-----------------------------------------------------------------------
    84 c   Depthts:
    85 c   --------
     75      REAL,SAVE :: dz1(nsoilmx),dz2(nsoilmx)
     76      REAL,allocatable,save :: zc(:,:),zd(:,:)
     77      REAL,SAVE :: lambda
     78      LOGICAL,SAVE :: firstcall=.true.
     79
     80c-----------------------------------------------------------------------
     81c   Depths:
     82c   -------
    8683
    8784      REAL fz,rk,fz1,rk1,rk2
    8885      fz(rk)=fz1*(dalph_soil**rk-1.)/(dalph_soil-1.)
     86
    8987      pfluxgrd(:) = 0.
    9088 
     89      ! on Venus thermal inertia is assumed constant over the globe
    9190      DO ig = 1, knon
    9291          ztherm_i(ig)   = inertie
     
    9594      IF (firstcall) THEN
    9695
    97       allocate(zc(klon,nsoilmx),zd(klon,nsoilmx))
     96         allocate(zc(klon,nsoilmx),zd(klon,nsoilmx))
    9897
    9998c-----------------------------------------------------------------------
     
    103102
    104103c VENUS : A REVOIR !!!!
    105          min_period=20000. ! en secondes
    106          dalph_soil=2.    ! rapport entre les epaisseurs de 2 couches succ.
     104         min_period=20000. ! in seconds
     105         dalph_soil=2.    ! ratio between successive layer sizes
    107106
    108107         OPEN(99,file='soil.def',status='old',form='formatted',err=9999)
     
    1151149999     CONTINUE
    116115
    117 c   la premiere couche represente un dixieme de cycle diurne
     116c   The first soil layer depth, based on min_period
    118117         fz1=sqrt(min_period/3.14)
    119118
     
    137136     .               fz(rk1)*fz(rk2)*3.14,fz(rk)*fz(rk)*3.14
    138137         ENDDO
     138         
     139c-----------------------------------------------------------------------
     140c   Computation of the Cgrd and Dgrd coefficient for the next step:
     141c   ---------------------------------------------------------------
     142         DO jk=1,nsoilmx
     143            zdz2(jk)=dz2(jk)/ptimestep
     144         ENDDO
     145
     146         DO ig=1,knon
     147            z1(ig)=zdz2(nsoilmx)+dz1(nsoilmx-1)
     148            zc(ig,nsoilmx-1)=
     149     $          zdz2(nsoilmx)*ptsoil(ig,nsoilmx)/z1(ig)
     150            zd(ig,nsoilmx-1)=dz1(nsoilmx-1)/z1(ig)
     151         ENDDO
     152
     153         DO jk=nsoilmx-1,2,-1
     154            DO ig=1,knon
     155               z1(ig)=1./(zdz2(jk)+dz1(jk-1)+dz1(jk)
     156     $            *(1.-zd(ig,jk)))
     157               zc(ig,jk-1)=
     158     s         (ptsoil(ig,jk)*zdz2(jk)+dz1(jk)*zc(ig,jk))
     159     $             *z1(ig)
     160               zd(ig,jk-1)=dz1(jk-1)*z1(ig)
     161            ENDDO
     162         ENDDO
    139163         firstcall =.false.
    140164
    141       ELSE   !--not firstcall
     165      ENDIF !--not firstcall
     166
    142167c-----------------------------------------------------------------------
    143168c   Computation of the soil temperatures using the Cgrd and Dgrd
     
    145170c  -----------------------------------------------
    146171
    147 c    surface temperature
     172c        temperature in the first soil layer
    148173         DO ig=1,knon
    149174            ptsoil(ig,1)=(lambda*zc(ig,1)+ptsrf(ig))/
     
    151176         ENDDO
    152177
    153 c   other temperatures
     178c        temperatures in the other soil layers
    154179         DO jk=1,nsoilmx-1
    155180            DO ig=1,knon
     
    158183         ENDDO
    159184
    160       ENDIF !--not firstcall
    161185c-----------------------------------------------------------------------
    162186c   Computation of the Cgrd and Dgrd coefficient for the next step:
     
    204228      ENDDO
    205229
    206       RETURN
     230     
    207231      END
Note: See TracChangeset for help on using the changeset viewer.