Ignore:
Timestamp:
Feb 25, 2014, 10:59:48 AM (11 years ago)
Author:
emillour
Message:

Common dynamics: a couple of bug fixes:

  • Correctly account for the change in pressure, mass, etc. after modifying surface pressure following a call to the physics.
  • Corrected tracer advection, which is computed using values at the beginning of the time step, so it is done at Matsuno forward step.

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/addfi.F

    r7 r1189  
    5555c    -----------
    5656c
    57       REAL pdt
     57      REAL,INTENT(IN) :: pdt ! time step for the integration (s)
    5858c
    59       REAL pvcov(ip1jm,llm),pucov(ip1jmp1,llm)
    60       REAL pteta(ip1jmp1,llm),pq(ip1jmp1,llm,nqtot),pps(ip1jmp1)
     59      REAL,INTENT(INOUT) :: pvcov(ip1jm,llm) ! covariant meridional wind
     60      REAL,INTENT(INOUT) :: pucov(ip1jmp1,llm) ! covariant zonal wind
     61      REAL,INTENT(INOUT) :: pteta(ip1jmp1,llm) ! potential temperature
     62      REAL,INTENT(INOUT) :: pq(ip1jmp1,llm,nqtot) ! tracers
     63      REAL,INTENT(INOUT) :: pps(ip1jmp1) ! surface pressure (Pa)
     64c respective tendencies (.../s) to add
     65      REAL,INTENT(IN) :: pdvfi(ip1jm,llm)
     66      REAL,INTENT(IN) :: pdufi(ip1jmp1,llm)
     67      REAL,INTENT(IN) :: pdqfi(ip1jmp1,llm,nqtot)
     68      REAL,INTENT(IN) :: pdhfi(ip1jmp1,llm)
     69      REAL,INTENT(IN) :: pdpfi(ip1jmp1)
    6170c
    62       REAL pdvfi(ip1jm,llm),pdufi(ip1jmp1,llm)
    63       REAL pdqfi(ip1jmp1,llm,nqtot),pdhfi(ip1jmp1,llm),pdpfi(ip1jmp1)
    64 c
    65       LOGICAL leapf,forward
     71      LOGICAL,INTENT(IN) :: leapf,forward ! not used
    6672c
    6773c
     
    7177      REAL xpn(iim),xps(iim),tpn,tps
    7278      INTEGER j,k,iq,ij
    73       REAL qtestw, qtestt
    74       PARAMETER ( qtestw = 1.0e-15 )
    75       PARAMETER ( qtestt = 1.0e-40 )
     79      REAL,PARAMETER :: qtestw = 1.0e-15
     80      REAL,PARAMETER :: qtestt = 1.0e-40
    7681
    7782      REAL SSUM
  • trunk/LMDZ.COMMON/libf/dyn3d/advtrac.F90

    r1019 r1189  
    99  !            M.A Filiberti (04/2002)
    1010  !
    11   USE infotrac
    12   USE control_mod
     11  USE infotrac, ONLY: nqtot, iadv
     12  USE control_mod, ONLY: iapp_tracvl, day_step
    1313
    1414
     
    3030  !     Arguments
    3131  !-------------------------------------------------------------------
     32  INTEGER,INTENT(OUT) :: iapptrac
     33  REAL,INTENT(IN) :: pbaru(ip1jmp1,llm)
     34  REAL,INTENT(IN) :: pbarv(ip1jm,llm)
     35  REAL,INTENT(INOUT) :: q(ip1jmp1,llm,nqtot)
     36  REAL,INTENT(IN) :: masse(ip1jmp1,llm)
     37  REAL,INTENT(IN) :: p( ip1jmp1,llmp1 )
     38  REAL,INTENT(IN) :: teta(ip1jmp1,llm)
     39  REAL,INTENT(IN) :: pk(ip1jmp1,llm)
     40  REAL,INTENT(OUT) :: flxw(ip1jmp1,llm)
     41  !-------------------------------------------------------------------
    3242  !     Ajout PPM
    3343  !--------------------------------------------------------
    3444  REAL massebx(ip1jmp1,llm),masseby(ip1jm,llm)
    35   !--------------------------------------------------------
    36   INTEGER iapptrac
    37   REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
    38   REAL q(ip1jmp1,llm,nqtot),masse(ip1jmp1,llm)
    39   REAL p( ip1jmp1,llmp1 ),teta(ip1jmp1,llm)
    40   REAL pk(ip1jmp1,llm)
    41   REAL flxw(ip1jmp1,llm)
    42 
    4345  !-------------------------------------------------------------
    4446  !     Variables locales
  • trunk/LMDZ.COMMON/libf/dyn3d/caldyn.F

    r5 r1189  
    11!
    2 ! $Header$
     2! $Id: $
    33!
    4 c
    5 c
    64      SUBROUTINE caldyn
    75     $ (itau,ucov,vcov,teta,ps,masse,pk,pkf,tsurpk,phis ,
     
    108      IMPLICIT NONE
    119
    12 c=======================================================================
    13 c
    14 c  Auteur :  P. Le Van
    15 c
    16 c   Objet:
    17 c   ------
    18 c
    19 c   Calcul des tendances dynamiques.
    20 c
    21 c Modif 04/93 F.Forget
    22 c=======================================================================
     10!=======================================================================
     11!
     12!  Auteur :  P. Le Van
     13!
     14!   Objet:
     15!   ------
     16!
     17!   Calcul des tendances dynamiques.
     18!
     19! Modif 04/93 F.Forget
     20!=======================================================================
    2321
    24 c-----------------------------------------------------------------------
    25 c   0. Declarations:
    26 c   ----------------
     22!-----------------------------------------------------------------------
     23!   0. Declarations:
     24!   ----------------
    2725
    2826#include "dimensions.h"
     
    3230#include "comgeom.h"
    3331
    34 c   Arguments:
    35 c   ----------
     32!   Arguments:
     33!   ----------
    3634
    37       LOGICAL conser
     35      LOGICAL,INTENT(IN) :: conser ! triggers printing some diagnostics
     36      INTEGER,INTENT(IN) :: itau ! time step index
     37      REAL,INTENT(IN) :: vcov(ip1jm,llm) ! covariant meridional wind
     38      REAL,INTENT(IN) :: ucov(ip1jmp1,llm) ! covariant zonal wind
     39      REAL,INTENT(IN) :: teta(ip1jmp1,llm) ! potential temperature
     40      REAL,INTENT(IN) :: ps(ip1jmp1) ! surface pressure
     41      REAL,INTENT(IN) :: phis(ip1jmp1) ! geopotential at the surface
     42      REAL,INTENT(IN) :: pk(ip1jmp1,llm) ! Exner at mid-layer
     43      REAL,INTENT(IN) :: pkf(ip1jmp1,llm) ! filtered Exner
     44      REAL,INTENT(IN) :: tsurpk(ip1jmp1,llm) ! cpp * temperature / pk
     45      REAL,INTENT(IN) :: phi(ip1jmp1,llm) ! geopotential
     46      REAL,INTENT(OUT) :: masse(ip1jmp1,llm) ! air mass
     47      REAL,INTENT(OUT) :: dv(ip1jm,llm) ! tendency on vcov
     48      REAL,INTENT(OUT) :: du(ip1jmp1,llm) ! tendency on ucov
     49      REAL,INTENT(OUT) :: dteta(ip1jmp1,llm) ! tenddency on teta
     50      REAL,INTENT(OUT) :: dp(ip1jmp1) ! tendency on ps
     51      REAL,INTENT(OUT) :: w(ip1jmp1,llm) ! vertical velocity
     52      REAL,INTENT(OUT) :: pbaru(ip1jmp1,llm) ! mass flux in the zonal direction
     53      REAL,INTENT(OUT) :: pbarv(ip1jm,llm) ! mass flux in the meridional direction
     54      REAL,INTENT(IN) :: time ! current time
    3855
    39       INTEGER itau
    40       REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
    41       REAL ps(ip1jmp1),phis(ip1jmp1)
    42       REAL pk(ip1jmp1,llm),pkf(ip1jmp1,llm)
    43       REAL tsurpk(ip1jmp1,llm)
     56!   Local:
     57!   ------
     58
    4459      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
    45       REAL phi(ip1jmp1,llm),masse(ip1jmp1,llm)
    46       REAL dv(ip1jm,llm),du(ip1jmp1,llm)
    47       REAL dteta(ip1jmp1,llm),dp(ip1jmp1)
    48       REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
    49       REAL time
    50 
    51 c   Local:
    52 c   ------
    53 
    5460      REAL ang(ip1jmp1,llm),p(ip1jmp1,llmp1)
    5561      REAL massebx(ip1jmp1,llm),masseby(ip1jm,llm),psexbarxy(ip1jm)
    5662      REAL vorpot(ip1jm,llm)
    57       REAL w(ip1jmp1,llm),ecin(ip1jmp1,llm),convm(ip1jmp1,llm)
     63      REAL ecin(ip1jmp1,llm),convm(ip1jmp1,llm)
    5864      REAL bern(ip1jmp1,llm)
    5965      REAL massebxy(ip1jm,llm)
     
    6268      INTEGER   ij,l
    6369
    64 c-----------------------------------------------------------------------
    65 c   Calcul des tendances dynamiques:
    66 c   --------------------------------
     70!-----------------------------------------------------------------------
     71!   Compute dynamical tendencies:
     72!--------------------------------
    6773
     74      ! compute contravariant winds ucont() and vcont
    6875      CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
     76      ! compute pressure p()
    6977      CALL pression ( ip1jmp1, ap      , bp   ,  ps  , p            )
     78      ! compute psexbarxy() XY-area weighted-averaged surface pressure (what for?)
    7079      CALL psextbar (   ps   , psexbarxy                            )
     80      ! compute mass in each atmospheric mesh: masse()
    7181      CALL massdair (    p   , masse                                )
     82      ! compute X and Y-averages of mass, massebx() and masseby()
    7283      CALL massbar  (   masse, massebx , masseby                    )
     84      ! compute XY-average of mass, massebxy()
    7385      call massbarxy(   masse, massebxy                             )
     86      ! compute mass fluxes pbaru() and pbarv()
    7487      CALL flumass  ( massebx, masseby , vcont, ucont ,pbaru, pbarv )
     88      ! compute dteta() , horizontal converging flux of theta
    7589      CALL dteta1   (   teta , pbaru   , pbarv, dteta               )
     90      ! compute convm(), horizontal converging flux of mass
    7691      CALL convmas  (   pbaru, pbarv   , convm                      )
    7792
     93      ! compute pressure variation due to mass convergence
    7894      DO ij =1, ip1jmp1
    7995         dp( ij ) = convm( ij,1 ) / airesurg( ij )
    8096      ENDDO
    8197
     98      ! compute vertical velocity w()
    8299      CALL vitvert ( convm  , w                                  )
     100      ! compute potential vorticity vorpot()
    83101      CALL tourpot ( vcov   , ucov  , massebxy  , vorpot         )
     102      ! compute rotation induced du() and dv()
    84103      CALL dudv1   ( vorpot , pbaru , pbarv     , du     , dv    )
     104      ! compute kinetic energy ecin()
    85105      CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
     106      ! compute Bernouilli function bern()
    86107      CALL bernoui ( ip1jmp1, llm   , phi       , ecin   , bern  )
     108      ! compute and add du() and dv() contributions from Bernouilli and pressure
    87109      CALL dudv2   ( tsurpk , pkf   , bern      , du     , dv    )
    88110
     
    94116      ENDDO
    95117
    96 
     118      ! compute vertical advection contributions to du(), dv() and dteta()
    97119      CALL advect( ang, vcov, teta, w, massebx, masseby, du, dv,dteta )
    98120
    99 C  WARNING probleme de peridocite de dv sur les PC/linux. Pb d'arrondi
    100 C          probablement. Observe sur le code compile avec pgf90 3.0-1
     121!  WARNING probleme de peridocite de dv sur les PC/linux. Pb d'arrondi
     122!          probablement. Observe sur le code compile avec pgf90 3.0-1
    101123
    102124      DO l = 1, llm
    103125         DO ij = 1, ip1jm, iip1
    104126           IF( dv(ij,l).NE.dv(ij+iim,l) )  THEN
    105 c         PRINT *,'!!!ATTENTION!!! probleme de periodicite sur vcov', 
    106 c    ,   ' dans caldyn'
    107 c         PRINT *,' l,  ij = ', l, ij, ij+iim,dv(ij+iim,l),dv(ij,l)
     127!         PRINT *,'!!!ATTENTION!!! probleme de periodicite sur vcov', 
     128!    ,   ' dans caldyn'
     129!         PRINT *,' l,  ij = ', l, ij, ij+iim,dv(ij+iim,l),dv(ij,l)
    108130          dv(ij+iim,l) = dv(ij,l)
    109131          endif
    110132         enddo
    111133      enddo
    112 c-----------------------------------------------------------------------
    113 c   Sorties eventuelles des variables de controle:
    114 c   ----------------------------------------------
     134
     135!-----------------------------------------------------------------------
     136!   Output some control variables:
     137!---------------------------------
    115138
    116139      IF( conser )  THEN
     
    120143      ENDIF
    121144
    122       RETURN
    123145      END
  • trunk/LMDZ.COMMON/libf/dyn3d/calfis.F

    r1129 r1189  
    2929c    Auteur :  P. Le Van, F. Hourdin
    3030c   .........
    31       USE infotrac
    32       USE control_mod
     31      USE infotrac, ONLY: nqtot, niadv, tname
     32      USE control_mod, ONLY: planet_type, nsplit_phys
    3333      USE write_field
    3434      USE cpdet_mod, only: t2tpot,tpot2t
     
    106106c    Arguments :
    107107c    -----------
    108       LOGICAL  lafin
    109 
    110 
    111       REAL pvcov(iip1,jjm,llm)
    112       REAL pucov(iip1,jjp1,llm)
    113       REAL pteta(iip1,jjp1,llm)
    114       REAL pmasse(iip1,jjp1,llm)
    115       REAL pq(iip1,jjp1,llm,nqtot)
    116       REAL pphis(iip1,jjp1)
    117       REAL pphi(iip1,jjp1,llm)
    118 
    119       REAL pdvcov(iip1,jjm,llm)
    120       REAL pducov(iip1,jjp1,llm)
    121       REAL pdteta(iip1,jjp1,llm)
     108      LOGICAL,INTENT(IN) ::  lafin ! .true. for the very last call to physics
     109      REAL,INTENT(IN) :: jD_cur, jH_cur
     110      REAL,INTENT(IN) :: pvcov(iip1,jjm,llm) ! covariant meridional velocity
     111      REAL,INTENT(IN) :: pucov(iip1,jjp1,llm) ! covariant zonal velocity
     112      REAL,INTENT(IN) :: pteta(iip1,jjp1,llm) ! potential temperature
     113      REAL,INTENT(IN) :: pmasse(iip1,jjp1,llm) ! mass in each cell ! not used
     114      REAL,INTENT(IN) :: pq(iip1,jjp1,llm,nqtot) ! tracers
     115      REAL,INTENT(IN) :: pphis(iip1,jjp1) ! surface geopotential
     116      REAL,INTENT(IN) :: pphi(iip1,jjp1,llm) ! geopotential
     117
     118      REAL,INTENT(IN) :: pdvcov(iip1,jjm,llm) ! dynamical tendency on vcov
     119      REAL,INTENT(IN) :: pducov(iip1,jjp1,llm) ! dynamical tendency on ucov
     120      REAL,INTENT(IN) :: pdteta(iip1,jjp1,llm) ! dynamical tendency on teta
    122121! commentaire SL: pdq ne sert que pour le calcul de pcvgq,
    123122! qui lui meme ne sert a rien dans la routine telle qu'elle est
    124123! ecrite, et que j'ai donc commente....
    125       REAL pdq(iip1,jjp1,llm,nqtot)
    126 
    127       REAL pps(iip1,jjp1)
    128       REAL pp(iip1,jjp1,llmp1)
    129       REAL ppk(iip1,jjp1,llm)
    130 
    131 c TENDENCIES in */s
    132       REAL pdvfi(iip1,jjm,llm)
    133       REAL pdufi(iip1,jjp1,llm)
    134       REAL pdhfi(iip1,jjp1,llm)
    135       REAL pdqfi(iip1,jjp1,llm,nqtot)
    136       REAL pdpsfi(iip1,jjp1)
     124      REAL,INTENT(IN) :: pdq(iip1,jjp1,llm,nqtot) ! dynamical tendency on tracers
     125      ! NB: pdq is only used to compute pcvgq which is in fact not used...
     126
     127      REAL,INTENT(IN) :: pps(iip1,jjp1) ! surface pressure (Pa)
     128      REAL,INTENT(IN) :: pp(iip1,jjp1,llmp1) ! pressure at mesh interfaces (Pa)
     129      REAL,INTENT(IN) :: ppk(iip1,jjp1,llm) ! Exner at mid-layer
     130      REAL,INTENT(IN) :: flxw(iip1,jjp1,llm)  ! Vertical mass flux on dynamics grid
     131
     132      ! tendencies (in */s) from the physics
     133      REAL,INTENT(OUT) :: pdvfi(iip1,jjm,llm) ! tendency on covariant meridional wind
     134      REAL,INTENT(OUT) :: pdufi(iip1,jjp1,llm) ! tendency on covariant zonal wind
     135      REAL,INTENT(OUT) :: pdhfi(iip1,jjp1,llm) ! tendency on potential temperature (K/s)
     136      REAL,INTENT(OUT) :: pdqfi(iip1,jjp1,llm,nqtot) ! tendency on tracers
     137      REAL,INTENT(OUT) :: pdpsfi(iip1,jjp1) ! tendency on surface pressure (Pa/s)
    137138
    138139
     
    173174
    174175cIM diagnostique PVteta, Amip2
    175       INTEGER ntetaSTD
    176       PARAMETER(ntetaSTD=3)
    177       REAL rtetaSTD(ntetaSTD)
    178       DATA rtetaSTD/350., 380., 405./ ! Earth-specific values, beware !!
     176      INTEGER,PARAMETER :: ntetaSTD=3
     177      REAL,SAVE :: rtetaSTD(ntetaSTD)=(/350.,380.,405./) ! Earth-specific, beware !!
    179178      REAL PVteta(ngridmx,ntetaSTD)
    180179
    181       REAL flxw(iip1,jjp1,llm)  ! Flux de masse verticale sur la grille dynamique
    182180      REAL flxwfi(ngridmx,llm)  ! Flux de masse verticale sur la grille physiq
    183181     
    184182      REAL SSUM
    185183
    186       LOGICAL firstcal, debut
    187       DATA firstcal/.true./
    188       SAVE firstcal,debut
     184      LOGICAL,SAVE :: firstcal=.true., debut=.true.
    189185!      REAL rdayvrai
    190       REAL, intent(in):: jD_cur, jH_cur
    191186
    192187      LOGICAL tracerdyn ! for generic/mars physics call ; possibly to get rid of
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F

    r1056 r1189  
    174174      starttime = 0
    175175      CALL getin('starttime',starttime)
    176 
     176     
     177      ! Mars: time of start for run in "start.nc" (when there are multiple time
     178      !       steps stored in the file)
     179      timestart=-9999 ! default value; if <0, use last stored time
     180      call getin("timestart",timestart)
     181     
    177182!Config  Key  = less1day
    178183!Config  Desc = Possibilite d'integrer moins d'un jour
  • trunk/LMDZ.COMMON/libf/dyn3d/dissip.F

    r1 r1189  
    11!
    2 ! $Header$
     2! $Id: $
    33!
    44      SUBROUTINE dissip( vcov,ucov,teta,p, dv,du,dh )
     
    3535c   ----------
    3636
    37       REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
    38       REAL  p( ip1jmp1,llmp1 )
    39       REAL dv(ip1jm,llm),du(ip1jmp1,llm),dh(ip1jmp1,llm)
     37      REAL,INTENT(IN) :: vcov(ip1jm,llm) ! covariant meridional wind
     38      REAL,INTENT(IN) :: ucov(ip1jmp1,llm) ! covariant zonal wind
     39      REAL,INTENT(IN) :: teta(ip1jmp1,llm) ! potential temperature
     40      REAL,INTENT(IN) :: p(ip1jmp1,llmp1) ! pressure
     41      ! tendencies (.../s) on covariant winds and potential temperature
     42      REAL,INTENT(OUT) :: dv(ip1jm,llm)
     43      REAL,INTENT(OUT) :: du(ip1jmp1,llm)
     44      REAL,INTENT(OUT) :: dh(ip1jmp1,llm)
    4045
    4146c   Local:
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r1107 r1189  
    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, only: planet_type,nday,day_step,iperiod,iphysiq,
     16      USE write_field, ONLY: writefield
     17      USE control_mod, ONLY: planet_type,nday,day_step,iperiod,iphysiq,
    1818     &                       less1day,fractday,ndynstep,iconser,
    1919     &                       dissip_period,offline,ip_ebil_dyn,
     
    7575! #include "clesphys.h"
    7676
    77       real zqmin,zqmax
    78 
    79 c   variables dynamiques
    80       REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    81       REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    82       REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
    83       REAL ps(ip1jmp1)                       ! pression  au sol
    84       REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
    85       REAL pks(ip1jmp1)                      ! exner au  sol
    86       REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
    87       REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
    88       REAL masse(ip1jmp1,llm)                ! masse d'air
    89       REAL phis(ip1jmp1)                     ! geopotentiel au sol
    90       REAL phi(ip1jmp1,llm)                  ! geopotentiel
    91       REAL w(ip1jmp1,llm)                    ! vitesse verticale
     77      REAL,INTENT(IN) :: time_0 ! not used
     78
     79c   dynamical variables:
     80      REAL,INTENT(INOUT) :: ucov(ip1jmp1,llm)    ! zonal covariant wind
     81      REAL,INTENT(INOUT) :: vcov(ip1jm,llm)      ! meridional covariant wind
     82      REAL,INTENT(INOUT) :: teta(ip1jmp1,llm)    ! potential temperature
     83      REAL,INTENT(INOUT) :: ps(ip1jmp1)          ! surface pressure (Pa)
     84      REAL,INTENT(INOUT) :: masse(ip1jmp1,llm)   ! air mass
     85      REAL,INTENT(INOUT) :: phis(ip1jmp1)        ! geopotentiat at the surface
     86      REAL,INTENT(INOUT) :: q(ip1jmp1,llm,nqtot) ! advected tracers
     87
     88      REAL p (ip1jmp1,llmp1  )               ! interlayer pressure
     89      REAL pks(ip1jmp1)                      ! exner at the surface
     90      REAL pk(ip1jmp1,llm)                   ! exner at mid-layer
     91      REAL pkf(ip1jmp1,llm)                  ! filtered exner at mid-layer
     92      REAL phi(ip1jmp1,llm)                  ! geopotential
     93      REAL w(ip1jmp1,llm)                    ! vertical velocity
    9294! ADAPTATION GCM POUR CP(T)
    9395      REAL temp(ip1jmp1,llm)                 ! temperature 
    9496      REAL tsurpk(ip1jmp1,llm)               ! cpp*T/pk 
     97
     98      real zqmin,zqmax
    9599
    96100c variables dynamiques intermediaire pour le transport
     
    133137
    134138      REAL  SSUM
    135       REAL time_0
    136139!     REAL finvmaold(ip1jmp1,llm)
    137140
     
    410413c   -------------------------------------------------------------
    411414
    412 !      IF( forward. OR . leapf )  THEN
    413 ! Ehouarn: NB: at this point p with ps are not synchronized
    414 !              (whereas mass and ps are...)
    415       IF((.not.forward).OR. leapf )  THEN
    416         ! Ehouarn: gather mass fluxes during backward Matsuno or LF step
     415      IF( forward. OR . leapf )  THEN
     416! Ehouarn: NB: fields sent to advtrac are those at the beginning of the time step
    417417         CALL caladvtrac(q,pbaru,pbarv,
    418418     *        p, masse, dq,  teta,
     
    547547     $                  ucov, vcov, teta , q   ,ps ,
    548548     $                 dufi, dvfi, dtetafi , dqfi ,dpfi  )
    549 
     549          ! since addfi updates ps(), also update p(), masse() and pk()
     550          CALL pression (ip1jmp1,ap,bp,ps,p)
     551          CALL massdair(p,masse)
     552          if (pressure_exner) then
     553            CALL exner_hyb(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf)
     554          else
     555            CALL exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf)
     556          endif
     557         
    550558c      Couche superieure :
    551559c      -------------------
     
    600608          CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    601609        endif
    602 
     610        CALL massdair(p,masse)
    603611
    604612c-----------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.