Ignore:
Timestamp:
Sep 7, 2012, 2:49:58 PM (12 years ago)
Author:
emillour
Message:

Common dynamics: updates to keep up with LMDZ5 Earth (rev 1649)
See file "DOC/chantiers/commit_importants.log" for details.
EM

File:
1 edited

Legend:

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

    r500 r776  
    124124
    125125      REAL  SSUM
    126       REAL time_0 , finvmaold(ip1jmp1,llm)
     126      REAL time_0
     127!     REAL finvmaold(ip1jmp1,llm)
    127128
    128129cym      LOGICAL  lafin
     
    243244      dq(:,:,:)=0.
    244245      CALL pression ( ip1jmp1, ap, bp, ps, p       )
    245       if (disvert_type==1) then
     246      if (pressure_exner) then
    246247        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
    247       else ! we assume that we are in the disvert_type==2 case
     248      else
    248249        CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    249250      endif
     
    271272c   ----------------------------------
    272273
    273    1  CONTINUE
     274   1  CONTINUE ! Matsuno Forward step begins here
    274275
    275276      jD_cur = jD_ref + day_ini - day_ref +                             &
    276      &          int (itau * dtvr / daysec)
     277     &          itau/day_step
    277278      jH_cur = jH_ref + start_time +                                    &
    278      &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     279     &          mod(itau,day_step)/float(day_step)
    279280      jD_cur = jD_cur + int(jH_cur)
    280281      jH_cur = jH_cur - int(jH_cur)
     
    307308
    308309c   ...    P.Le Van .26/04/94  ....
    309 
    310       CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
    311       CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
    312 
    313    2  CONTINUE
     310! Ehouarn: finvmaold is actually not used
     311!      CALL SCOPY   ( ijp1llm,   masse, 1, finvmaold,     1 )
     312!      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
     313
     314   2  CONTINUE ! Matsuno backward or leapfrog step begins here
    314315
    315316c-----------------------------------------------------------------------
     
    357358      call tpot2t(ijp1llm,teta,temp,pk)
    358359      tsurpk = cpp*temp/pk
     360      ! compute geopotential phi()
    359361      CALL geopot  ( ip1jmp1, tsurpk  , pk , pks,  phis  , phi   )
    360362
     
    372374
    373375!      IF( forward. OR . leapf )  THEN
     376! Ehouarn: NB: at this point p with ps are not synchronized
     377!              (whereas mass and ps are...)
    374378      IF((.not.forward).OR. leapf )  THEN
    375379        ! Ehouarn: gather mass fluxes during backward Matsuno or LF step
     
    398402
    399403       CALL integrd ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
    400      $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
    401      $              finvmaold                                    )
     404     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis )
     405!     $              finvmaold                                    )
    402406
    403407       IF ((planet_type.eq."titan").and.(tidal)) then
     
    431435
    432436         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
    433          if (disvert_type==1) then
     437         if (pressure_exner) then
    434438           CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
    435          else ! we assume that we are in the disvert_type==2 case
     439         else
    436440           CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    437441         endif
    438442
    439443           jD_cur = jD_ref + day_ini - day_ref +                        &
    440      &          int (itau * dtvr / daysec)
     444     &          itau/day_step
    441445           jH_cur = jH_ref + start_time +                               &
    442      &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     446     &          mod(itau,day_step)/float(day_step)
    443447           jD_cur = jD_cur + int(jH_cur)
    444448           jH_cur = jH_cur - int(jH_cur)
     
    545549
    546550        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
    547         if (disvert_type==1) then
     551        if (pressure_exner) then
    548552          CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
    549         else ! we assume that we are in the disvert_type==2 case
     553        else
    550554          CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    551555        endif
     
    613617        ENDDO
    614618
    615         DO ij =  1,iim
    616           tppn(ij)  = aire(  ij    ) * ps (  ij    )
    617           tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
    618         ENDDO
    619           tpn  = SSUM(iim,tppn,1)/apoln
    620           tps  = SSUM(iim,tpps,1)/apols
    621 
    622         DO ij = 1, iip1
    623           ps(  ij    ) = tpn
    624           ps(ij+ip1jm) = tps
    625         ENDDO
    626 
     619        if (1 == 0) then
     620!!! Ehouarn: lines here 1) kill 1+1=2 in the dynamics
     621!!!                     2) should probably not be here anyway
     622!!! but are kept for those who would want to revert to previous behaviour
     623           DO ij =  1,iim
     624             tppn(ij)  = aire(  ij    ) * ps (  ij    )
     625             tpps(ij)  = aire(ij+ip1jm) * ps (ij+ip1jm)
     626           ENDDO
     627             tpn  = SSUM(iim,tppn,1)/apoln
     628             tps  = SSUM(iim,tpps,1)/apols
     629
     630           DO ij = 1, iip1
     631             ps(  ij    ) = tpn
     632             ps(ij+ip1jm) = tps
     633           ENDDO
     634        endif ! of if (1 == 0)
    627635
    628636      END IF ! of IF(apdiss)
     
    749757
    750758              CLOSE(99)
     759              !!! Ehouarn: Why not stop here and now?
    751760            ENDIF ! of IF (itau.EQ.itaufin)
    752761
Note: See TracChangeset for help on using the changeset viewer.