Ignore:
Timestamp:
Jun 11, 2014, 3:46:46 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r1997:2055 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3d/leapfrog.F

    r1999 r2056  
    1919     &                       iecri, ip_ebil_dyn, ok_dynzon, ok_dyn_ins,
    2020     &                       periodav, ok_dyn_ave, output_grads_dyn
     21      use exner_hyb_m, only: exner_hyb
     22      use exner_milieu_m, only: exner_milieu
     23
    2124      IMPLICIT NONE
    2225
     
    158161      character*10 string10
    159162
    160       REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm)
    161163      REAL :: flxw(ip1jmp1,llm)  ! flux de masse verticale
    162164
     
    196198
    197199
    198       itaufin   = nday*day_step
     200      if (nday>=0) then
     201         itaufin   = nday*day_step
     202      else
     203         itaufin   = -nday
     204      endif
    199205      itaufinp1 = itaufin +1
    200206      itau = 0
     
    217223      CALL pression ( ip1jmp1, ap, bp, ps, p       )
    218224      if (pressure_exner) then
    219         CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
     225        CALL exner_hyb( ip1jmp1, ps, p, pks, pk, pkf )
    220226      else
    221         CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
     227        CALL exner_milieu( ip1jmp1, ps, p, pks, pk, pkf )
    222228      endif
    223229
     
    373379         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
    374380         if (pressure_exner) then
    375            CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
     381           CALL exner_hyb(  ip1jmp1, ps, p,pks, pk, pkf )
    376382         else
    377            CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
     383           CALL exner_milieu( ip1jmp1, ps, p, pks, pk, pkf )
    378384         endif
     385
     386! Appel a geopot ajoute le 2014/05/08 pour garantir la convergence numerique
     387! avec dyn3dmem
     388         CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    379389
    380390!           rdaym_ini  = itau * dtvr / daysec
     
    448458          CALL massdair(p,masse)
    449459          if (pressure_exner) then
    450             CALL exner_hyb(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf)
     460            CALL exner_hyb(ip1jmp1,ps,p,pks,pk,pkf)
    451461          else
    452             CALL exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf)
     462            CALL exner_milieu(ip1jmp1,ps,p,pks,pk,pkf)
    453463          endif
    454464
     
    506516        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
    507517        if (pressure_exner) then
    508           CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
     518          CALL exner_hyb( ip1jmp1, ps, p, pks, pk, pkf )
    509519        else
    510           CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
     520          CALL exner_milieu( ip1jmp1, ps, p, pks, pk, pkf )
    511521        endif
    512522        CALL massdair(p,masse)
Note: See TracChangeset for help on using the changeset viewer.