New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 4772 for branches/2014/dev_r4650_UKMO7_STARTHOUR – NEMO

Ignore:
Timestamp:
2014-09-17T19:19:59+02:00 (10 years ago)
Author:
djlea
Message:

Changes to allow hour start time. First version.

Location:
branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r4624 r4772  
    1717   !!---------------------------------------------------------------------- 
    1818   !!   asm_inc_init   : Initialize the increment arrays and IAU weights 
    19    !!   calc_date      : Compute the calendar date YYYYMMDD on a given step 
     19   !!   calc_date      : Compute the calendar date YYYYMMDDHH on a given step 
    2020   !!   tra_asm_inc    : Apply the tracer (T and S) increments 
    2121   !!   dyn_asm_inc    : Apply the dynamic (u and v) increments 
     
    4545    
    4646   PUBLIC   asm_inc_init   !: Initialize the increment arrays and IAU weights 
    47    PUBLIC   calc_date      !: Compute the calendar date YYYYMMDD on a given step 
     47   PUBLIC   calc_date      !: Compute the calendar date YYYYMMDDHH on a given step 
    4848   PUBLIC   tra_asm_inc    !: Apply the tracer (T and S) increments 
    4949   PUBLIC   dyn_asm_inc    !: Apply the dynamic (u and v) increments 
     
    115115      INTEGER :: iiauper         ! Number of time steps in the IAU period 
    116116      INTEGER :: icycper         ! Number of time steps in the cycle 
    117       INTEGER :: iitend_date     ! Date YYYYMMDD of final time step 
    118       INTEGER :: iitbkg_date     ! Date YYYYMMDD of background time step for Jb term 
    119       INTEGER :: iitdin_date     ! Date YYYYMMDD of background time step for DI 
    120       INTEGER :: iitiaustr_date  ! Date YYYYMMDD of IAU interval start time step 
    121       INTEGER :: iitiaufin_date  ! Date YYYYMMDD of IAU interval final time step 
     117      INTEGER :: iitend_date     ! Date YYYYMMDDHH of final time step 
     118      INTEGER :: iitbkg_date     ! Date YYYYMMDDHH of background time step for Jb term 
     119      INTEGER :: iitdin_date     ! Date YYYYMMDDHH of background time step for DI 
     120      INTEGER :: iitiaustr_date  ! Date YYYYMMDDHH of IAU interval start time step 
     121      INTEGER :: iitiaufin_date  ! Date YYYYMMDDHH of IAU interval final time step 
    122122      INTEGER :: ios             ! Local integer output status for namelist read 
    123123 
     
    556556      !!                    ***  ROUTINE calc_date  *** 
    557557      !!           
    558       !! ** Purpose : Compute the calendar date YYYYMMDD at a given time step. 
    559       !! 
    560       !! ** Method  : Compute the calendar date YYYYMMDD at a given time step. 
     558      !! ** Purpose : Compute the calendar date YYYYMMDDHH at a given time step. 
     559      !! 
     560      !! ** Method  : Compute the calendar date YYYYMMDDHH at a given time step. 
    561561      !! 
    562562      !! ** Action  :  
     
    570570      INTEGER :: imon0    ! Initial month 
    571571      INTEGER :: iday0    ! Initial day 
     572      INTEGER :: ihou0    ! Initial hour 
    572573      INTEGER :: iyea     ! Current year 
    573574      INTEGER :: imon     ! Current month 
    574575      INTEGER :: iday     ! Current day 
     576      INTEGER :: ihou     ! Current hour 
    575577      INTEGER :: idaystp  ! Number of days between initial and current date 
     578      INTEGER :: ihoustp  ! Number of hours 
    576579      INTEGER :: idaycnt  ! Day counter 
    577580 
     
    579582 
    580583      !----------------------------------------------------------------------- 
    581       ! Compute the calendar date YYYYMMDD 
     584      ! Compute the calendar date YYYYMMDDHH 
    582585      !----------------------------------------------------------------------- 
    583586 
     
    585588      iyea0 =   kdate0 / 10000 
    586589      imon0 = ( kdate0 - ( iyea0 * 10000 ) ) / 100 
    587       iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 )  
     590      iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 ) 
     591      ihou0 = nn_time0  
    588592 
    589593      ! Check that kt >= kit000 - 1 
    590594      IF ( kt < kit000 - 1 ) CALL ctl_stop( ' kt must be >= kit000 - 1') 
    591595 
    592       ! If kt = kit000 - 1 then set the date to the restart date 
    593       IF ( kt == kit000 - 1 ) THEN 
    594  
    595          kdate = ndastp 
    596          RETURN 
    597  
    598       ENDIF 
    599  
    600596      ! Compute the number of days from the initial date 
    601597      idaystp = INT( REAL( kt - kit000 ) * rdt / 86400. ) 
    602     
     598      ihoustp = INT( REAL( kt - kit000 ) * rdt / 3600. ) - ( idaystp * 24 ) 
     599 
    603600      iday    = iday0 
    604601      imon    = imon0 
    605602      iyea    = iyea0 
     603      ihou    = ihou0 
    606604      idaycnt = 0 
     605 
     606      ! Increment hours 
     607      ihou = ihou + ihoustp 
     608      IF ( ihou >= 24 ) THEN 
     609         ihou = ihou - 24 
     610         iday = iday + 1 
     611      ENDIF 
    607612 
    608613      CALL calc_month_len( iyea, imonth_len ) 
     
    611616         iday = iday + 1 
    612617         IF ( iday > imonth_len(imon) )  THEN 
    613             iday = 1 
     618            iday = iday - imonth_len(imon) 
    614619            imon = imon + 1 
    615620         ENDIF 
     
    622627      END DO 
    623628      ! 
    624       kdate = iyea * 10000 + imon * 100 + iday 
     629      kdate = iyea * 1000000 + imon * 10000 + iday * 100 + ihou 
    625630      ! 
    626631   END SUBROUTINE 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r4162 r4772  
    8484      IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
    8585 
     86      ! If we are starting at 00Z then need to wind back to previous day for calendar initialisation  
     87      IF( nn_time0 .eq. 0 ) ndastp = ndastp - 1  
     88 
    8689      ! set the calandar from ndastp (read in restart file and namelist) 
    8790 
     
    9093      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
    9194 
    92       CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday )  ! we assume that we start run at 00:00 
     95      CALL ymds2ju( nyear, nmonth, nday, nn_time0*3600._wp, fjulday )  ! we assume that we start run at 00:00 
    9396      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error 
    94       fjulday = fjulday + 1.                             ! move back to the day at nit000 (and not at nit000 - 1) 
     97      IF( nn_time0 == 0 ) fjulday = fjulday + 1.                       ! move back to the day at nit000 (and not at nit000 - 1) 
    9598 
    9699      nsec1jan000 = 0 
     
    117120 
    118121      ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step 
    119       nsec_year  = nday_year * nsecd - ndt05   ! 1 time step before the middle of the first time step 
    120       nsec_month = nday      * nsecd - ndt05   ! because day will be called at the beginning of step 
    121       nsec_week  = idweek    * nsecd - ndt05 
    122       nsec_day   =             nsecd - ndt05 
    123  
     122      nsec_year  = nday_year * nsecd + nn_time0*3600._wp - ndt05   ! 1 time step before the middle of the first time step 
     123      nsec_month = nday      * nsecd + nn_time0*3600._wp - ndt05   ! because day will be called at the beginning of step 
     124      nsec_week  = idweek    * nsecd + nn_time0*3600._wp - ndt05 
     125      nsec_day   =             nsecd + nn_time0*3600._wp - ndt05 
     126      IF( nsec_day .lt. 0 ) nsec_day = nsec_day + nsecd 
     127       
    124128      ! control print 
    125129      IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i6)')' ==============>> 1/2 time step before the start of the run DATE Y/M/D = ',   & 
     
    327331            ! define ndastp and adatrj 
    328332            IF ( nrstdt == 2 ) THEN 
    329                ! read the parameters correspondting to nit000 - 1 (last time step of previous run) 
     333               ! read the parameters corresponding to nit000 - 1 (last time step of previous run) 
    330334               CALL iom_get( numror, 'ndastp', zndastp ) 
    331335               ndastp = NINT( zndastp ) 
    332336               CALL iom_get( numror, 'adatrj', adatrj  ) 
    333337            ELSE 
    334                ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    335                ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
     338               ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
     339               ndastp = ndate0        ! ndate0 read in the namelist in dom_nam 
    336340               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    337341               ! note this is wrong if time step has changed during run 
    338342            ENDIF 
    339343         ELSE 
    340             ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    341             ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
     344            ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
     345            ndastp = ndate0           ! ndate0 read in the namelist in dom_nam 
    342346            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    343347         ENDIF 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r4624 r4772  
    135135      !!---------------------------------------------------------------------- 
    136136      USE ioipsl 
    137       NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   & 
    138          &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    139          &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz, nn_euler 
     137      NAMELIST/namrun/ nn_no   , cn_exp  , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,  & 
     138         &             nn_it000, nn_itend, nn_date0    , nn_time0     , nn_leapy  , nn_istate ,  & 
     139         &             nn_stock, nn_write, ln_dimgnnn  , ln_mskland   , ln_clobber, nn_chunksz,  & 
     140         &             nn_euler              
    140141      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    141142         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
     
    176177         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    177178         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
     179         WRITE(numout,*) '      initial time of day in hours    nn_time0   = ', nn_time0 
    178180         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    179181         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r4624 r4772  
    3434   INTEGER       ::   nn_itend         !: index of the last time step 
    3535   INTEGER       ::   nn_date0         !: initial calendar date aammjj 
     36   INTEGER       ::   nn_time0         !: initial time of day in hours 
    3637   INTEGER       ::   nn_leapy         !: Leap year calendar flag (0/1 or 30) 
    3738   INTEGER       ::   nn_istate        !: initial state output flag (0/1) 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r4624 r4772  
    14141414   END SUBROUTINE dia_obs_dealloc 
    14151415 
    1416    SUBROUTINE ini_date( ddobsini ) 
    1417       !!---------------------------------------------------------------------- 
    1418       !!                    ***  ROUTINE ini_date  *** 
     1416   SUBROUTINE calc_date( kstp, ddobs ) 
     1417      !!---------------------------------------------------------------------- 
     1418      !!                    ***  ROUTINE calc_date  *** 
    14191419      !!           
    1420       !! ** Purpose : Get initial data in double precision YYYYMMDD.HHMMSS format 
    1421       !! 
    1422       !! ** Method  : Get initial data in double precision YYYYMMDD.HHMMSS format 
    1423       !! 
    1424       !! ** Action  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     1420      !! ** Purpose : Get date in double precision YYYYMMDD.HHMMSS format 
     1421      !! 
     1422      !! ** Method  : Get date in double precision YYYYMMDD.HHMMSS format 
     1423      !! 
     1424      !! ** Action  : Get date in double precision YYYYMMDD.HHMMSS format 
    14251425      !! 
    14261426      !! History : 
     
    14301430      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date 
    14311431      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     1432      !!        !  2014-09  (D. Lea) New generic routine now deals with arbitrary start hour  
    14321433      !!---------------------------------------------------------------------- 
    14331434      USE phycst, ONLY : &            ! Physical constants 
     
    14411442 
    14421443      !! * Arguments 
    1443       REAL(KIND=dp), INTENT(OUT) :: ddobsini                         ! Initial date in YYYYMMDD.HHMMSS 
     1444      REAL(KIND=dp), INTENT(OUT) :: ddobs                        ! Date in YYYYMMDD.HHMMSS 
     1445      INTEGER :: kstp 
    14441446 
    14451447      !! * Local declarations 
     
    14561458      !!---------------------------------------------------------------------- 
    14571459      !! Initial date initialization (year, month, day, hour, minute) 
    1458       !! (This assumes that the initial date is for 00z)) 
    14591460      !!---------------------------------------------------------------------- 
    14601461      iyea =   ndate0 / 10000 
    14611462      imon = ( ndate0 - iyea * 10000 ) / 100 
    14621463      iday =   ndate0 - iyea * 10000 - imon * 100 
    1463       ihou = 0 
     1464      ihou = nn_time0 
    14641465      imin = 0 
    14651466 
     
    14671468      !! Compute number of days + number of hours + min since initial time 
    14681469      !!---------------------------------------------------------------------- 
    1469       iday = iday + ( nit000 -1 ) * rdt / rday 
    1470       zdayfrc = ( nit000 -1 ) * rdt / rday 
     1470      zdayfrc = kstp * rdt / rday 
    14711471      zdayfrc = zdayfrc - aint(zdayfrc) 
    1472       ihou = int( zdayfrc * 24 ) 
    1473       imin = int( (zdayfrc * 24 - ihou) * 60 ) 
     1472      imin = imin + int( zdayfrc * 24 * 60 )  
     1473      DO WHILE (imin >= 60)  
     1474        imin=imin-60 
     1475        ihou=ihou+1 
     1476      END DO 
     1477      DO WHILE (ihou >= 24) 
     1478        ihou=ihou-24 
     1479        iday=iday+1 
     1480      END DO  
     1481      iday = iday + kstp * rdt / rday  
    14741482 
    14751483      !!----------------------------------------------------------------------- 
     
    14921500      !! Convert it into YYYYMMDD.HHMMSS format. 
    14931501      !!---------------------------------------------------------------------- 
    1494       ddobsini = iyea * 10000_dp + imon * 100_dp + & 
    1495          &       iday + ihou * 0.01_dp + imin * 0.0001_dp 
    1496  
    1497  
    1498    END SUBROUTINE ini_date 
    1499  
    1500    SUBROUTINE fin_date( ddobsfin ) 
    1501       !!---------------------------------------------------------------------- 
    1502       !!                    ***  ROUTINE fin_date  *** 
     1502      ddobs = iyea * 10000_dp + imon * 100_dp + & 
     1503         &    iday + ihou * 0.01_dp + imin * 0.0001_dp 
     1504 
     1505   END SUBROUTINE calc_date 
     1506 
     1507   SUBROUTINE ini_date( ddobsini ) 
     1508      !!---------------------------------------------------------------------- 
     1509      !!                    ***  ROUTINE ini_date  *** 
    15031510      !!           
    1504       !! ** Purpose : Get final data in double precision YYYYMMDD.HHMMSS format 
    1505       !! 
    1506       !! ** Method  : Get final data in double precision YYYYMMDD.HHMMSS format 
    1507       !! 
    1508       !! ** Action  : Get final data in double precision YYYYMMDD.HHMMSS format 
     1511      !! ** Purpose : Get initial date in double precision YYYYMMDD.HHMMSS format 
     1512      !! 
     1513      !! ** Method  :  
     1514      !! 
     1515      !! ** Action  :  
    15091516      !! 
    15101517      !! History : 
     
    15131520      !!        !  06-10  (A. Weaver) Cleaning 
    15141521      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
    1515       !!---------------------------------------------------------------------- 
    1516       USE phycst, ONLY : &            ! Physical constants 
    1517          & rday 
    1518 !      USE daymod, ONLY : &            ! Time variables 
    1519 !         & nmonth_len                 
    1520       USE dom_oce, ONLY : &           ! Ocean space and time domain variables 
    1521          & rdt 
     1522      !!        !  2014-09  (D. Lea) Change to call generic routine calc_date 
     1523      !!---------------------------------------------------------------------- 
     1524 
     1525      IMPLICIT NONE 
     1526 
     1527      !! * Arguments 
     1528      REAL(KIND=dp), INTENT(OUT) :: ddobsini                   ! Initial date in YYYYMMDD.HHMMSS 
     1529 
     1530      CALL calc_date( nit000 - 1, ddobsini ) 
     1531 
     1532   END SUBROUTINE ini_date 
     1533 
     1534   SUBROUTINE fin_date( ddobsfin ) 
     1535      !!---------------------------------------------------------------------- 
     1536      !!                    ***  ROUTINE fin_date  *** 
     1537      !!           
     1538      !! ** Purpose : Get final date in double precision YYYYMMDD.HHMMSS format 
     1539      !! 
     1540      !! ** Method  :  
     1541      !! 
     1542      !! ** Action  :  
     1543      !! 
     1544      !! History : 
     1545      !!        !  06-03  (K. Mogensen)  Original code 
     1546      !!        !  06-05  (K. Mogensen)  Reformatted 
     1547      !!        !  06-10  (A. Weaver) Cleaning 
     1548      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     1549      !!        !  2014-09  (D. Lea) Change to call generic routine calc_date 
     1550      !!---------------------------------------------------------------------- 
    15221551 
    15231552      IMPLICIT NONE 
     
    15261555      REAL(KIND=dp), INTENT(OUT) :: ddobsfin                   ! Final date in YYYYMMDD.HHMMSS 
    15271556 
    1528       !! * Local declarations 
    1529       INTEGER :: iyea        ! date - (year, month, day, hour, minute) 
    1530       INTEGER :: imon 
    1531       INTEGER :: iday 
    1532       INTEGER :: ihou 
    1533       INTEGER :: imin 
    1534       INTEGER :: imday         ! Number of days in month. 
    1535       REAL(KIND=wp) :: zdayfrc       ! Fraction of day 
    1536           
    1537       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    1538              
    1539       !----------------------------------------------------------------------- 
    1540       ! Initial date initialization (year, month, day, hour, minute) 
    1541       ! (This assumes that the initial date is for 00z) 
    1542       !----------------------------------------------------------------------- 
    1543       iyea =   ndate0 / 10000 
    1544       imon = ( ndate0 - iyea * 10000 ) / 100 
    1545       iday =   ndate0 - iyea * 10000 - imon * 100 
    1546       ihou = 0 
    1547       imin = 0 
    1548        
    1549       !----------------------------------------------------------------------- 
    1550       ! Compute number of days + number of hours + min since initial time 
    1551       !----------------------------------------------------------------------- 
    1552       iday    = iday +  nitend  * rdt / rday 
    1553       zdayfrc =  nitend  * rdt / rday 
    1554       zdayfrc = zdayfrc - AINT( zdayfrc ) 
    1555       ihou    = INT( zdayfrc * 24 ) 
    1556       imin    = INT( ( zdayfrc * 24 - ihou ) * 60 ) 
    1557  
    1558       !----------------------------------------------------------------------- 
    1559       ! Convert number of days (iday) into a real date 
    1560       !---------------------------------------------------------------------- 
    1561  
    1562       CALL calc_month_len( iyea, imonth_len ) 
    1563        
    1564       DO WHILE ( iday > imonth_len(imon) ) 
    1565          iday = iday - imonth_len(imon) 
    1566          imon = imon + 1  
    1567          IF ( imon > 12 ) THEN 
    1568             imon = 1 
    1569             iyea = iyea + 1 
    1570             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    1571          ENDIF 
    1572       END DO 
    1573  
    1574       !----------------------------------------------------------------------- 
    1575       ! Convert it into YYYYMMDD.HHMMSS format 
    1576       !----------------------------------------------------------------------- 
    1577       ddobsfin = iyea * 10000_dp + imon * 100_dp    + iday & 
    1578          &     + ihou * 0.01_dp  + imin * 0.0001_dp 
    1579  
    1580     END SUBROUTINE fin_date 
    1581      
     1557      CALL calc_date( nitend, ddobsfin ) 
     1558 
     1559   END SUBROUTINE fin_date 
     1560    
    15821561END MODULE diaobs 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r4292 r4772  
    125125      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    126126      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    127       ihou0 = 0 
     127      ihou0 = nn_time0 
    128128      imin0 = 0 
    129129 
     
    397397      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    398398      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    399       ihou0 = 0 
     399      ihou0 = nn_time0 
    400400      imin0 = 0 
    401401 
     
    585585      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    586586      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    587       ihou0 = 0 
     587      ihou0 = nn_time0 
    588588      imin0 = 0 
    589589 
     
    770770      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    771771      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    772       ihou0 = 0 
     772      ihou0 = nn_time0 
    773773      imin0 = 0 
    774774 
     
    968968      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    969969      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    970       ihou0 = 0 
     970      ihou0 = nn_time0 
    971971      imin0 = 0 
    972972 
Note: See TracChangeset for help on using the changeset viewer.