Ignore:
Timestamp:
Dec 10, 2009, 10:02:56 AM (15 years ago)
Author:
Laurent Fairhead
Message:

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/dyn3d/leapfrog.F

    r1146 r1279  
     1!
     2! $Id$
    13!
    24c
     
    1113#endif
    1214      USE infotrac
    13 
     15      USE guide_mod, ONLY : guide_main
     16      USE write_field
    1417      IMPLICIT NONE
    1518
     
    111114c
    112115      INTEGER itau,itaufinp1,iav
    113       INTEGER*4  iday ! jour julien
    114       REAL       time ! Heure de la journee en fraction d'1 jour
     116!      INTEGER  iday ! jour julien
     117      REAL       time
    115118
    116119      REAL  SSUM
     
    124127      real time_step, t_wrt, t_ops
    125128
    126       REAL rdayvrai,rdaym_ini
     129!      REAL rdayvrai,rdaym_ini
     130! jD_cur: jour julien courant
     131! jH_cur: heure julienne courante
     132      REAL :: jD_cur, jH_cur
     133      INTEGER :: an, mois, jour
     134      REAL :: secondes
     135
    127136      LOGICAL first,callinigrads
    128137cIM : pour sortir les param. du modele dans un fis. netcdf 110106
    129138      save first
    130139      data first/.true./
    131       real dt_cum, zjulian
     140      real dt_cum
    132141      character*10 infile
    133142      integer zan, tau0, thoriid
     
    166175      character*80 abort_message
    167176
    168 C Calendrier
    169       LOGICAL true_calendar
    170       PARAMETER (true_calendar = .false.)
    171 
    172177      logical dissip_conservative
    173178      save dissip_conservative
     
    192197
    193198      itau = 0
    194       iday = day_ini+itau/day_step
    195       time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    196          IF(time.GT.1.) THEN
    197           time = time-1.
    198           iday = iday+1
    199          ENDIF
     199c$$$      iday = day_ini+itau/day_step
     200c$$$      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     201c$$$         IF(time.GT.1.) THEN
     202c$$$          time = time-1.
     203c$$$          iday = iday+1
     204c$$$         ENDIF
    200205
    201206
     
    214219   1  CONTINUE
    215220
     221      jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec)
     222      jH_cur = jH_ref +                                                 &
     223     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     224
    216225
    217226#ifdef CPP_IOIPSL
    218       if (ok_guide.and.(itaufin-itau-1)*dtvr.gt.21600) then
    219         call guide(itau,ucov,vcov,teta,q,masse,ps)
    220       else
    221         IF(prt_level>9)WRITE(lunout,*)'leapfrog: attention on ne ',
    222      .    'guide pas les 6 dernieres heures'
     227      if (ok_guide) then
     228        call guide_main(itau,ucov,vcov,teta,q,masse,ps)
    223229      endif
    224230#endif
     231
     232
    225233c
    226234c     IF( MOD( itau, 10* day_step ).EQ.0 )  THEN
     
    284292      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
    285293
     294      time = jD_cur + jH_cur
    286295      CALL caldyn
    287296     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
    288      $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time+iday-day_ini )
     297     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time )
     298
    289299
    290300c-----------------------------------------------------------------------
     
    344354         CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
    345355
    346            rdaym_ini  = itau * dtvr / daysec
    347            rdayvrai   = rdaym_ini  + day_ini
    348 
     356!           rdaym_ini  = itau * dtvr / daysec
     357!           rdayvrai   = rdaym_ini  + day_ini
     358           jD_cur = jD_ref + day_ini - day_ref
     359     $        + int (itau * dtvr / daysec)
     360           jH_cur = jH_ref +                                            &
     361     &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
     362!         write(lunout,*)'itau, jD_cur = ', itau, jD_cur, jH_cur
     363!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
     364!         write(lunout,*)'current date = ',an, mois, jour, secondes
    349365
    350366c rajout debug
     
    378394#endif
    379395! #endif of #ifdef CPP_IOIPSL
    380          CALL calfis( lafin ,rdayvrai,time  ,
     396         CALL calfis( lafin , jD_cur, jH_cur,
    381397     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    382398     $               du,dv,dteta,dq,
     
    385401
    386402         IF (ok_strato) THEN
    387            CALL top_bound( vcov,ucov,teta, dufi,dvfi,dtetafi)
     403           CALL top_bound( vcov,ucov,teta,masse,dufi,dvfi,dtetafi)
    388404         ENDIF
    389405       
     
    506522            IF(forward. OR. leapf) THEN
    507523              itau= itau + 1
    508               iday= day_ini+itau/day_step
    509               time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    510                 IF(time.GT.1.) THEN
    511                   time = time-1.
    512                   iday = iday+1
    513                 ENDIF
     524c$$$              iday= day_ini+itau/day_step
     525c$$$              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     526c$$$                IF(time.GT.1.) THEN
     527c$$$                  time = time-1.
     528c$$$                  iday = iday+1
     529c$$$                ENDIF
    514530            ENDIF
    515531
     
    517533            IF( itau. EQ. itaufinp1 ) then 
    518534              if (flag_verif) then
    519                 write(80,*) 'ucov',ucov
    520                 write(81,*) 'vcov',vcov
    521                 write(82,*) 'teta',teta
    522                 write(83,*) 'ps',ps
    523                 write(84,*) 'q',q
     535                write(79,*) 'ucov',ucov
     536                write(80,*) 'vcov',vcov
     537                write(81,*) 'teta',teta
     538                write(82,*) 'ps',ps
     539                write(83,*) 'q',q
    524540                WRITE(85,*) 'q1 = ',q(:,:,1)
    525541                WRITE(86,*) 'q3 = ',q(:,:,3)
    526                 write(90) ucov
    527                 write(91) vcov
    528                 write(92) teta
    529                 write(93) ps
    530                 write(94) q
    531542              endif
    532543
     
    548559               IF (ok_dynzon) THEN
    549560#ifdef CPP_IOIPSL
    550                   CALL writedynav(histaveid, itau,vcov ,
    551      ,                 ucov,teta,pk,phi,q,masse,ps,phis)
     561!                  CALL writedynav(histaveid, itau,vcov ,
     562!     ,                 ucov,teta,pk,phi,q,masse,ps,phis)
    552563                  CALL bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
    553564     ,                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     
    586597
    587598              if (planet_type.eq."earth") then
    588 #ifdef CPP_EARTH
    589599! Write an Earth-format restart file
    590600                CALL dynredem1("restart.nc",0.0,
    591601     &                         vcov,ucov,teta,q,masse,ps)
    592 #endif
    593602              endif ! of if (planet_type.eq."earth")
    594603
     
    636645
    637646             itau =  itau + 1
    638              iday = day_ini+itau/day_step
    639              time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
    640 
    641                   IF(time.GT.1.) THEN
    642                    time = time-1.
    643                    iday = iday+1
    644                   ENDIF
     647c$$$             iday = day_ini+itau/day_step
     648c$$$             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     649c$$$
     650c$$$                  IF(time.GT.1.) THEN
     651c$$$                   time = time-1.
     652c$$$                   iday = iday+1
     653c$$$                  ENDIF
    645654
    646655               forward =  .FALSE.
     
    662671               IF (ok_dynzon) THEN
    663672#ifdef CPP_IOIPSL
    664                   CALL writedynav(histaveid, itau,vcov ,
    665      ,                 ucov,teta,pk,phi,q,masse,ps,phis)
     673!                  CALL writedynav(histaveid, itau,vcov ,
     674!     ,                 ucov,teta,pk,phi,q,masse,ps,phis)
    666675                  CALL bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
    667676     ,                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     
    693702              IF(itau.EQ.itaufin) THEN
    694703                if (planet_type.eq."earth") then
    695 #ifdef CPP_EARTH
    696704                  CALL dynredem1("restart.nc",0.0,
    697705     &                           vcov,ucov,teta,q,masse,ps)
    698 #endif
    699706                endif ! of if (planet_type.eq."earth")
    700707              ENDIF ! of IF(itau.EQ.itaufin)
Note: See TracChangeset for help on using the changeset viewer.