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/dyn3dmem/leapfrog_loc.F

    r1999 r2056  
    3131       USE call_calfis_mod, ONLY : call_calfis
    3232       USE leapfrog_mod
     33       use exner_hyb_loc_m, only: exner_hyb_loc
     34       use exner_milieu_loc_m, only: exner_milieu_loc
    3335      IMPLICIT NONE
    3436
     
    156158      character*10 string10
    157159
    158 !      REAL,SAVE,ALLOCATABLE :: alpha(:,:),beta(:,:)
    159160!      REAL,SAVE,ALLOCATABLE :: flxw(:,:) ! flux de masse verticale
    160161
     
    213214      lafin=.false.
    214215     
    215       itaufin   = nday*day_step
     216      if (nday>=0) then
     217         itaufin   = nday*day_step
     218      else
     219         itaufin   = -nday
     220      endif
     221
    216222      itaufinp1 = itaufin +1
    217223
     
    261267!      ALLOCATE(dqfi_tmp(iip1,llm,nqtot))
    262268!      ALLOCATE(finvmaold(ijb_u:ije_u,llm))
    263 !      ALLOCATE(alpha(ijb_u:ije_u,llm),beta(ijb_u:ije_u,llm))
    264269!      ALLOCATE(flxw(ijb_u:ije_u,llm))
    265270!      ALLOCATE(ecin(ijb_u:ije_u,llm),ecin0(ijb_u:ije_u,llm))
     
    284289c$OMP END MASTER
    285290      if (pressure_exner) then
    286       CALL exner_hyb_loc( ijnb_u, ps, p,alpha,beta, pks, pk, pkf)
     291      CALL exner_hyb_loc( ijnb_u, ps, p, pks, pk, pkf)
    287292      else
    288         CALL exner_milieu_loc( ijnb_u, ps, p, beta, pks, pk, pkf )
     293        CALL exner_milieu_loc( ijnb_u, ps, p, pks, pk, pkf )
    289294      endif
    290295c-----------------------------------------------------------------------
     
    780785
    781786! c$OMP BARRIER
    782 !          CALL exner_hyb_loc(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
     787!          CALL exner_hyb_loc(  ip1jmp1, ps, p,pks, pk, pkf )
    783788! c$OMP BARRIER
    784789!            jD_cur = jD_ref + day_ini - day_ref
     
    11351140c$OMP BARRIER
    11361141        if (pressure_exner) then
    1137         CALL exner_hyb_loc( ijnb_u, ps, p,alpha,beta, pks, pk, pkf )
     1142        CALL exner_hyb_loc( ijnb_u, ps, p, pks, pk, pkf )
    11381143        else
    1139           CALL exner_milieu_loc( ijnb_u, ps, p, beta, pks, pk, pkf )
     1144          CALL exner_milieu_loc( ijnb_u, ps, p, pks, pk, pkf )
    11401145        endif
    11411146c$OMP BARRIER
Note: See TracChangeset for help on using the changeset viewer.