Ignore:
Timestamp:
Feb 24, 2014, 4:05:47 PM (11 years ago)
Author:
Ehouarn Millour
Message:

Add updating pressure, mass and Exner function (ie: all variables which depend on surface pressure) after adding physics tendencies (which include a surface pressure tendency).
Note that this change induces slight changes in GCM results with respect to previous svn version of the code, even if surface pressure tendency is zero (because of recomputation of polar values as an average over polar points on the dynamics grid).
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r1907 r1987  
    1212      use IOIPSL
    1313#endif
    14       USE infotrac
     14      USE infotrac, ONLY: nqtot
    1515      USE guide_mod, ONLY : guide_main
    16       USE write_field
    17       USE control_mod
     16      USE write_field, ONLY: writefield
     17      USE control_mod, ONLY: nday, day_step, planet_type, offline,
     18     &                       iconser, iphysiq, iperiod, dissip_period,
     19     &                       iecri, ip_ebil_dyn, ok_dynzon, ok_dyn_ins,
     20     &                       periodav, ok_dyn_ave, output_grads_dyn
    1821      IMPLICIT NONE
    1922
     
    6770! #include "clesphys.h"
    6871
    69       INTEGER         longcles
    70       PARAMETER     ( longcles = 20 )
    71       REAL  clesphy0( longcles )
     72      INTEGER,PARAMETER :: longcles = 20
     73      REAL,INTENT(IN) :: clesphy0( longcles ) ! not used
     74      REAL,INTENT(IN) :: time_0 ! not used
     75
     76c   dynamical variables:
     77      REAL,INTENT(INOUT) :: ucov(ip1jmp1,llm)    ! zonal covariant wind
     78      REAL,INTENT(INOUT) :: vcov(ip1jm,llm)      ! meridional covariant wind
     79      REAL,INTENT(INOUT) :: teta(ip1jmp1,llm)    ! potential temperature
     80      REAL,INTENT(INOUT) :: ps(ip1jmp1)          ! surface pressure (Pa)
     81      REAL,INTENT(INOUT) :: masse(ip1jmp1,llm)   ! air mass
     82      REAL,INTENT(INOUT) :: phis(ip1jmp1)        ! geopotentiat at the surface
     83      REAL,INTENT(INOUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers
     84
     85      REAL p (ip1jmp1,llmp1  )               ! interlayer pressure
     86      REAL pks(ip1jmp1)                      ! exner at the surface
     87      REAL pk(ip1jmp1,llm)                   ! exner at mid-layer
     88      REAL pkf(ip1jmp1,llm)                  ! filtered exner at mid-layer
     89      REAL phi(ip1jmp1,llm)                  ! geopotential
     90      REAL w(ip1jmp1,llm)                    ! vertical velocity
    7291
    7392      real zqmin,zqmax
    74 
    75 c   variables dynamiques
    76       REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    77       REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    78       REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
    79       REAL ps(ip1jmp1)                       ! pression  au sol
    80       REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
    81       REAL pks(ip1jmp1)                      ! exner au  sol
    82       REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
    83       REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
    84       REAL masse(ip1jmp1,llm)                ! masse d'air
    85       REAL phis(ip1jmp1)                     ! geopotentiel au sol
    86       REAL phi(ip1jmp1,llm)                  ! geopotentiel
    87       REAL w(ip1jmp1,llm)                    ! vitesse verticale
    8893
    8994c variables dynamiques intermediaire pour le transport
     
    117122
    118123      REAL  SSUM
    119       REAL time_0
    120124!     REAL finvmaold(ip1jmp1,llm)
    121125
     
    319323
    320324      IF( forward. OR . leapf )  THEN
    321 ! Ehouarn: NB: at this point p with ps are not synchronized
    322 !              (whereas mass and ps are...)
     325! Ehouarn: NB: fields sent to advtrac are those at the beginning of the time step
    323326         CALL caladvtrac(q,pbaru,pbarv,
    324327     *        p, masse, dq,  teta,
     
    441444     $                  ucov, vcov, teta , q   ,ps ,
    442445     $                 dufi, dvfi, dtetafi , dqfi ,dpfi  )
     446          ! since addfi updates ps(), also update p(), masse() and pk()
     447          CALL pression (ip1jmp1,ap,bp,ps,p)
     448          CALL massdair(p,masse)
     449          if (pressure_exner) then
     450            CALL exner_hyb(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf)
     451          else
     452            CALL exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf)
     453          endif
    443454
    444455         IF (ok_strato) THEN
     
    499510          CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    500511        endif
     512        CALL massdair(p,masse)
    501513
    502514
Note: See TracChangeset for help on using the changeset viewer.