summaryrefslogtreecommitdiffstats
path: root/academic/arpack/arpack-second-bug.patch
blob: 99998b26d290a836d65614043edd0a30ad097004 (plain)
diff -up ARPACK/UTIL/second.f.sb ARPACK/UTIL/second.f
--- ARPACK/UTIL/second.f.sb	1995-10-02 19:56:44.000000000 +0100
+++ ARPACK/UTIL/second.f	2007-10-24 02:50:57.000000000 +0200
@@ -1,4 +1,4 @@
-      SUBROUTINE SECOND( T )
+      SUBROUTINE secnd2( T )
 *
       REAL       T
 *
diff -up ARPACK/SRC/znaupd.f.sb ARPACK/SRC/znaupd.f
--- ARPACK/SRC/znaupd.f.sb	2002-08-15 07:50:57.000000000 +0200
+++ ARPACK/SRC/znaupd.f	2007-10-24 02:50:57.000000000 +0200
@@ -451,7 +451,7 @@ c        | & message level for debugging
 c        %-------------------------------%
 c
          call zstatn
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mcaupd
 c
 c        %----------------%
@@ -611,7 +611,7 @@ c
      &               '_naupd: Associated Ritz estimates')
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tcaupd = t1 - t0
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/dgetv0.f.sb ARPACK/SRC/dgetv0.f
--- ARPACK/SRC/dgetv0.f.sb	1999-04-08 00:42:47.000000000 +0200
+++ ARPACK/SRC/dgetv0.f	2007-10-24 02:50:57.000000000 +0200
@@ -214,7 +214,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mgetv0
 c 
          ierr   = 0
@@ -241,7 +241,7 @@ c        | Force the starting vector int
 c        | the generalized problem when B is possibly (singular).   |
 c        %----------------------------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nopx = nopx + 1
             ipntr(1) = 1
@@ -265,7 +265,7 @@ c
       if (orth)  go to 40
 c 
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
       end if
 c 
@@ -274,7 +274,7 @@ c     | Starting vector is now in the ra
 c     | Compute B-norm of starting vector.                   |
 c     %------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       first = .TRUE.
       if (bmat .eq. 'G') then
          nbx = nbx + 1
@@ -290,7 +290,7 @@ c 
    20 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -333,7 +333,7 @@ c     %---------------------------------
 c     | Compute the B-norm of the orthogonalized starting vector |
 c     %----------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       if (bmat .eq. 'G') then
          nbx = nbx + 1
          call dcopy (n, resid, 1, workd(n+1), 1)
@@ -348,7 +348,7 @@ c 
    40 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -406,7 +406,7 @@ c
       end if
       ido = 99
 c 
-      call second (t1)
+      call secnd2 (t1)
       tgetv0 = tgetv0 + (t1 - t0)
 c 
  9000 continue
diff -up ARPACK/SRC/ssgets.f.sb ARPACK/SRC/ssgets.f
--- ARPACK/SRC/ssgets.f.sb	1996-04-20 18:27:30.000000000 +0200
+++ ARPACK/SRC/ssgets.f	2007-10-24 02:50:57.000000000 +0200
@@ -148,7 +148,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = msgets
 c 
       if (which .eq. 'BE') then
@@ -198,7 +198,7 @@ c     
          call scopy (np, ritz, 1, shifts, 1)
       end if
 c 
-      call second (t1)
+      call secnd2 (t1)
       tsgets = tsgets + (t1 - t0)
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/snaup2.f.sb ARPACK/SRC/snaup2.f
--- ARPACK/SRC/snaup2.f.sb	2002-08-23 07:31:49.000000000 +0200
+++ ARPACK/SRC/snaup2.f	2007-10-24 02:50:57.000000000 +0200
@@ -258,7 +258,7 @@ c     %-----------------------%
 c
       if (ido .eq. 0) then
 c 
-         call second (t0)
+         call secnd2 (t0)
 c 
          msglvl = mnaup2
 c 
@@ -758,7 +758,7 @@ c        | the first step of the next ca
 c        %---------------------------------------------%
 c
          cnorm = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call scopy (n, resid, 1, workd(n+1), 1)
@@ -783,7 +783,7 @@ c        | WORKD(1:N) := B*RESID        
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -822,7 +822,7 @@ c     %------------%
 c     | Error Exit |
 c     %------------%
 c
-      call second (t1)
+      call secnd2 (t1)
       tnaup2 = t1 - t0
 c     
  9000 continue
diff -up ARPACK/SRC/dsgets.f.sb ARPACK/SRC/dsgets.f
--- ARPACK/SRC/dsgets.f.sb	1996-04-20 18:27:14.000000000 +0200
+++ ARPACK/SRC/dsgets.f	2007-10-24 02:50:57.000000000 +0200
@@ -148,7 +148,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = msgets
 c 
       if (which .eq. 'BE') then
@@ -198,7 +198,7 @@ c     
          call dcopy (np, ritz, 1, shifts, 1)
       end if
 c 
-      call second (t1)
+      call secnd2 (t1)
       tsgets = tsgets + (t1 - t0)
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/dsconv.f.sb ARPACK/SRC/dsconv.f
--- ARPACK/SRC/dsconv.f.sb	1996-04-20 18:27:11.000000000 +0200
+++ ARPACK/SRC/dsconv.f	2007-10-24 02:50:57.000000000 +0200
@@ -106,7 +106,7 @@ c     %-----------------------%
 c     | Executable Statements |
 c     %-----------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
 c
       eps23 = dlamch('Epsilon-Machine') 
       eps23 = eps23**(2.0D+0 / 3.0D+0)
@@ -126,7 +126,7 @@ c
 c
    10 continue
 c 
-      call second (t1)
+      call secnd2 (t1)
       tsconv = tsconv + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/dneigh.f.sb ARPACK/SRC/dneigh.f
--- ARPACK/SRC/dneigh.f.sb	1996-04-20 18:27:06.000000000 +0200
+++ ARPACK/SRC/dneigh.f	2007-10-24 02:50:57.000000000 +0200
@@ -170,7 +170,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mneigh
 c 
       if (msglvl .gt. 2) then
@@ -301,7 +301,7 @@ c
      &              '_neigh: Ritz estimates for the eigenvalues of H')
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tneigh = tneigh + (t1 - t0)
 c
  9000 continue
diff -up ARPACK/SRC/dsaitr.f.sb ARPACK/SRC/dsaitr.f
--- ARPACK/SRC/dsaitr.f.sb	1996-08-28 16:21:43.000000000 +0200
+++ ARPACK/SRC/dsaitr.f	2007-10-24 02:50:57.000000000 +0200
@@ -300,7 +300,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = msaitr
 c 
 c        %------------------------------%
@@ -420,7 +420,7 @@ c              | which spans OP and exit
 c              %------------------------------------------------%
 c
                info = j - 1
-               call second (t1)
+               call secnd2 (t1)
                tsaitr = tsaitr + (t1 - t0)
                ido = 99
                go to 9000
@@ -460,7 +460,7 @@ c        %------------------------------
 c
          step3 = .true.
          nopx  = nopx + 1
-         call second (t2)
+         call secnd2 (t2)
          call dcopy (n, v(1,j), 1, workd(ivj), 1)
          ipntr(1) = ivj
          ipntr(2) = irj
@@ -479,7 +479,7 @@ c        | Back from reverse communicati
 c        | WORKD(IRJ:IRJ+N-1) := OP*v_{j}.   |
 c        %-----------------------------------%
 c
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
 c 
          step3 = .false.
@@ -500,7 +500,7 @@ c        | assumed to have A*v_{j}.     
 c        %-------------------------------------------%
 c
          if (mode .eq. 2) go to 65
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             step4 = .true.
@@ -524,7 +524,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*OP*v_
 c        %-----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if 
 c
@@ -592,12 +592,12 @@ c
          else
             h(j,1) = rnorm
          end if
-         call second (t4)
+         call secnd2 (t4)
 c 
          orth1 = .true.
          iter  = 0
 c 
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call dcopy (n, resid, 1, workd(irj), 1)
@@ -621,7 +621,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*r_{j}
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -695,7 +695,7 @@ c
          h(j,2) = h(j,2) + workd(irj + j - 1)
 c 
          orth2 = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call dcopy (n, resid, 1, workd(irj), 1)
@@ -719,7 +719,7 @@ c        | Back from reverse communicati
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c
@@ -791,7 +791,7 @@ c 
          rstart = .false.
          orth2  = .false.
 c 
-         call second (t5)
+         call secnd2 (t5)
          titref = titref + (t5 - t4)
 c 
 c        %----------------------------------------------------------%
@@ -815,7 +815,7 @@ c        %------------------------------
 c
          j = j + 1
          if (j .gt. k+np) then
-            call second (t1)
+            call secnd2 (t1)
             tsaitr = tsaitr + (t1 - t0)
             ido = 99
 c
diff -up ARPACK/SRC/dnaup2.f.sb ARPACK/SRC/dnaup2.f
--- ARPACK/SRC/dnaup2.f.sb	2002-08-23 07:31:50.000000000 +0200
+++ ARPACK/SRC/dnaup2.f	2007-10-24 02:50:57.000000000 +0200
@@ -258,7 +258,7 @@ c     %-----------------------%
 c
       if (ido .eq. 0) then
 c 
-         call second (t0)
+         call secnd2 (t0)
 c 
          msglvl = mnaup2
 c 
@@ -758,7 +758,7 @@ c        | the first step of the next ca
 c        %---------------------------------------------%
 c
          cnorm = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call dcopy (n, resid, 1, workd(n+1), 1)
@@ -783,7 +783,7 @@ c        | WORKD(1:N) := B*RESID        
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -822,7 +822,7 @@ c     %------------%
 c     | Error Exit |
 c     %------------%
 c
-      call second (t1)
+      call secnd2 (t1)
       tnaup2 = t1 - t0
 c     
  9000 continue
diff -up ARPACK/SRC/cneigh.f.sb ARPACK/SRC/cneigh.f
--- ARPACK/SRC/cneigh.f.sb	1996-04-20 19:15:53.000000000 +0200
+++ ARPACK/SRC/cneigh.f	2007-10-24 02:50:57.000000000 +0200
@@ -171,7 +171,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mceigh
 c 
       if (msglvl .gt. 2) then
@@ -244,7 +244,7 @@ c
      &              '_neigh: Ritz estimates for the eigenvalues of H')
       end if
 c
-      call second(t1)
+      call secnd2(t1)
       tceigh = tceigh + (t1 - t0)
 c
  9000 continue
diff -up ARPACK/SRC/zngets.f.sb ARPACK/SRC/zngets.f
--- ARPACK/SRC/zngets.f.sb	1996-04-20 19:16:02.000000000 +0200
+++ ARPACK/SRC/zngets.f	2007-10-24 02:50:57.000000000 +0200
@@ -137,7 +137,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c 
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mcgets
 c 
       call zsortc (which, .true., kev+np, ritz, bounds)
@@ -157,7 +157,7 @@ c     
 c
       end if
 c     
-      call second (t1)
+      call secnd2 (t1)
       tcgets = tcgets + (t1 - t0)
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/sseigt.f.sb ARPACK/SRC/sseigt.f
--- ARPACK/SRC/sseigt.f.sb	1996-08-27 07:29:04.000000000 +0200
+++ ARPACK/SRC/sseigt.f	2007-10-24 02:50:57.000000000 +0200
@@ -138,7 +138,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------% 
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mseigt
 c
       if (msglvl .gt. 0) then
@@ -168,7 +168,7 @@ c
          bounds(k) = rnorm*abs(bounds(k))
    30 continue
 c 
-      call second (t1)
+      call secnd2 (t1)
       tseigt = tseigt + (t1 - t0)
 c
  9000 continue
diff -up ARPACK/SRC/dnapps.f.sb ARPACK/SRC/dnapps.f
--- ARPACK/SRC/dnapps.f.sb	1998-05-20 16:58:56.000000000 +0200
+++ ARPACK/SRC/dnapps.f	2007-10-24 02:50:57.000000000 +0200
@@ -237,7 +237,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mnapps
       kplusp = kev + np 
 c 
@@ -635,7 +635,7 @@ c
       end if
 c 
  9000 continue
-      call second (t1)
+      call secnd2 (t1)
       tnapps = tnapps + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/dsapps.f.sb ARPACK/SRC/dsapps.f
--- ARPACK/SRC/dsapps.f.sb	1998-05-20 16:58:59.000000000 +0200
+++ ARPACK/SRC/dsapps.f	2007-10-24 02:50:57.000000000 +0200
@@ -213,7 +213,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = msapps
 c 
       kplusp = kev + np 
@@ -503,7 +503,7 @@ c
          end if
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tsapps = tsapps + (t1 - t0)
 c 
  9000 continue 
diff -up ARPACK/SRC/ssaup2.f.sb ARPACK/SRC/ssaup2.f
--- ARPACK/SRC/ssaup2.f.sb	1998-05-20 16:58:59.000000000 +0200
+++ ARPACK/SRC/ssaup2.f	2007-10-24 02:50:57.000000000 +0200
@@ -262,7 +262,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = msaup2
 c
 c        %---------------------------------%
@@ -770,7 +770,7 @@ c        | the first step of the next ca
 c        %---------------------------------------------%
 c
          cnorm = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call scopy (n, resid, 1, workd(n+1), 1)
@@ -795,7 +795,7 @@ c        | WORKD(1:N) := B*RESID        
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -837,7 +837,7 @@ c     %------------%
 c     | Error exit |
 c     %------------%
 c
-      call second (t1)
+      call secnd2 (t1)
       tsaup2 = t1 - t0
 c 
  9000 continue
diff -up ARPACK/SRC/ssaitr.f.sb ARPACK/SRC/ssaitr.f
--- ARPACK/SRC/ssaitr.f.sb	1996-08-28 16:21:43.000000000 +0200
+++ ARPACK/SRC/ssaitr.f	2007-10-24 02:50:57.000000000 +0200
@@ -300,7 +300,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = msaitr
 c 
 c        %------------------------------%
@@ -420,7 +420,7 @@ c              | which spans OP and exit
 c              %------------------------------------------------%
 c
                info = j - 1
-               call second (t1)
+               call secnd2 (t1)
                tsaitr = tsaitr + (t1 - t0)
                ido = 99
                go to 9000
@@ -460,7 +460,7 @@ c        %------------------------------
 c
          step3 = .true.
          nopx  = nopx + 1
-         call second (t2)
+         call secnd2 (t2)
          call scopy (n, v(1,j), 1, workd(ivj), 1)
          ipntr(1) = ivj
          ipntr(2) = irj
@@ -479,7 +479,7 @@ c        | Back from reverse communicati
 c        | WORKD(IRJ:IRJ+N-1) := OP*v_{j}.   |
 c        %-----------------------------------%
 c
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
 c 
          step3 = .false.
@@ -500,7 +500,7 @@ c        | assumed to have A*v_{j}.     
 c        %-------------------------------------------%
 c
          if (mode .eq. 2) go to 65
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             step4 = .true.
@@ -524,7 +524,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*OP*v_
 c        %-----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if 
 c
@@ -592,12 +592,12 @@ c
          else
             h(j,1) = rnorm
          end if
-         call second (t4)
+         call secnd2 (t4)
 c 
          orth1 = .true.
          iter  = 0
 c 
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call scopy (n, resid, 1, workd(irj), 1)
@@ -621,7 +621,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*r_{j}
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -695,7 +695,7 @@ c
          h(j,2) = h(j,2) + workd(irj + j - 1)
 c 
          orth2 = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call scopy (n, resid, 1, workd(irj), 1)
@@ -719,7 +719,7 @@ c        | Back from reverse communicati
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c
@@ -791,7 +791,7 @@ c 
          rstart = .false.
          orth2  = .false.
 c 
-         call second (t5)
+         call secnd2 (t5)
          titref = titref + (t5 - t4)
 c 
 c        %----------------------------------------------------------%
@@ -815,7 +815,7 @@ c        %------------------------------
 c
          j = j + 1
          if (j .gt. k+np) then
-            call second (t1)
+            call secnd2 (t1)
             tsaitr = tsaitr + (t1 - t0)
             ido = 99
 c
diff -up ARPACK/SRC/snapps.f.sb ARPACK/SRC/snapps.f
--- ARPACK/SRC/snapps.f.sb	1998-05-20 16:58:55.000000000 +0200
+++ ARPACK/SRC/snapps.f	2007-10-24 02:50:57.000000000 +0200
@@ -237,7 +237,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mnapps
       kplusp = kev + np 
 c 
@@ -635,7 +635,7 @@ c
       end if
 c 
  9000 continue
-      call second (t1)
+      call secnd2 (t1)
       tnapps = tnapps + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/dnaitr.f.sb ARPACK/SRC/dnaitr.f
--- ARPACK/SRC/dnaitr.f.sb	1996-08-27 18:09:00.000000000 +0200
+++ ARPACK/SRC/dnaitr.f	2007-10-24 02:50:57.000000000 +0200
@@ -319,7 +319,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mnaitr
 c 
 c        %------------------------------%
@@ -430,7 +430,7 @@ c              | which spans OP and exit
 c              %------------------------------------------------%
 c
                info = j - 1
-               call second (t1)
+               call secnd2 (t1)
                tnaitr = tnaitr + (t1 - t0)
                ido = 99
                go to 9000
@@ -470,7 +470,7 @@ c        %------------------------------
 c
          step3 = .true.
          nopx  = nopx + 1
-         call second (t2)
+         call secnd2 (t2)
          call dcopy (n, v(1,j), 1, workd(ivj), 1)
          ipntr(1) = ivj
          ipntr(2) = irj
@@ -490,7 +490,7 @@ c        | WORKD(IRJ:IRJ+N-1) := OP*v_{j
 c        | if step3 = .true.                |
 c        %----------------------------------%
 c
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
  
          step3 = .false.
@@ -506,7 +506,7 @@ c        | STEP 4:  Finish extending the
 c        |          factorization to length j.   |
 c        %---------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             step4 = .true.
@@ -531,7 +531,7 @@ c        | if step4 = .true.            
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -576,11 +576,11 @@ c
 c
          if (j .gt. 1) h(j,j-1) = betaj
 c
-         call second (t4)
+         call secnd2 (t4)
 c 
          orth1 = .true.
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call dcopy (n, resid, 1, workd(irj), 1)
@@ -604,7 +604,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*r_{j}
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -681,7 +681,7 @@ c
          call daxpy (j, one, workd(irj), 1, h(1,j), 1)
 c 
          orth2 = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call dcopy (n, resid, 1, workd(irj), 1)
@@ -705,7 +705,7 @@ c        | Back from reverse communicati
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c
@@ -783,7 +783,7 @@ c 
          rstart = .false.
          orth2  = .false.
 c 
-         call second (t5)
+         call secnd2 (t5)
          titref = titref + (t5 - t4)
 c 
 c        %------------------------------------%
@@ -792,7 +792,7 @@ c        %------------------------------
 c
          j = j + 1
          if (j .gt. k+np) then
-            call second (t1)
+            call secnd2 (t1)
             tnaitr = tnaitr + (t1 - t0)
             ido = 99
             do 110 i = max(1,k), k+np-1
diff -up ARPACK/SRC/sneigh.f.sb ARPACK/SRC/sneigh.f
--- ARPACK/SRC/sneigh.f.sb	1996-04-20 18:27:22.000000000 +0200
+++ ARPACK/SRC/sneigh.f	2007-10-24 02:50:57.000000000 +0200
@@ -170,7 +170,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mneigh
 c 
       if (msglvl .gt. 2) then
@@ -301,7 +301,7 @@ c
      &              '_neigh: Ritz estimates for the eigenvalues of H')
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tneigh = tneigh + (t1 - t0)
 c
  9000 continue
diff -up ARPACK/SRC/dsaup2.f.sb ARPACK/SRC/dsaup2.f
--- ARPACK/SRC/dsaup2.f.sb	1998-05-20 16:59:00.000000000 +0200
+++ ARPACK/SRC/dsaup2.f	2007-10-24 02:50:57.000000000 +0200
@@ -262,7 +262,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = msaup2
 c
 c        %---------------------------------%
@@ -770,7 +770,7 @@ c        | the first step of the next ca
 c        %---------------------------------------------%
 c
          cnorm = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call dcopy (n, resid, 1, workd(n+1), 1)
@@ -795,7 +795,7 @@ c        | WORKD(1:N) := B*RESID        
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -837,7 +837,7 @@ c     %------------%
 c     | Error exit |
 c     %------------%
 c
-      call second (t1)
+      call secnd2 (t1)
       tsaup2 = t1 - t0
 c 
  9000 continue
diff -up ARPACK/SRC/snaupd.f.sb ARPACK/SRC/snaupd.f
--- ARPACK/SRC/snaupd.f.sb	2002-08-23 07:29:34.000000000 +0200
+++ ARPACK/SRC/snaupd.f	2007-10-24 02:50:57.000000000 +0200
@@ -476,7 +476,7 @@ c        | & message level for debugging
 c        %-------------------------------%
 c
          call sstatn
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mnaupd
 c
 c        %----------------%
@@ -640,7 +640,7 @@ c
      &               '_naupd: Associated Ritz estimates')
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tnaupd = t1 - t0
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/znapps.f.sb ARPACK/SRC/znapps.f
--- ARPACK/SRC/znapps.f.sb	1998-05-20 16:45:03.000000000 +0200
+++ ARPACK/SRC/znapps.f	2007-10-24 02:50:57.000000000 +0200
@@ -240,7 +240,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mcapps
 c 
       kplusp = kev + np 
@@ -495,7 +495,7 @@ c
       end if
 c
  9000 continue
-      call second (t1)
+      call secnd2 (t1)
       tcapps = tcapps + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/znaitr.f.sb ARPACK/SRC/znaitr.f
--- ARPACK/SRC/znaitr.f.sb	1996-08-27 18:12:57.000000000 +0200
+++ ARPACK/SRC/znaitr.f	2007-10-24 02:50:57.000000000 +0200
@@ -326,7 +326,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mcaitr
 c 
 c        %------------------------------%
@@ -437,7 +437,7 @@ c              | which spans OP and exit
 c              %------------------------------------------------%
 c
                info = j - 1
-               call second (t1)
+               call secnd2 (t1)
                tcaitr = tcaitr + (t1 - t0)
                ido = 99
                go to 9000
@@ -477,7 +477,7 @@ c        %------------------------------
 c
          step3 = .true.
          nopx  = nopx + 1
-         call second (t2)
+         call secnd2 (t2)
          call zcopy (n, v(1,j), 1, workd(ivj), 1)
          ipntr(1) = ivj
          ipntr(2) = irj
@@ -497,7 +497,7 @@ c        | WORKD(IRJ:IRJ+N-1) := OP*v_{j
 c        | if step3 = .true.                |
 c        %----------------------------------%
 c
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
  
          step3 = .false.
@@ -513,7 +513,7 @@ c        | STEP 4:  Finish extending the
 c        |          factorization to length j.   |
 c        %---------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             step4 = .true.
@@ -538,7 +538,7 @@ c        | if step4 = .true.            
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -583,11 +583,11 @@ c
 c
          if (j .gt. 1) h(j,j-1) = dcmplx(betaj, rzero)
 c
-         call second (t4)
+         call secnd2 (t4)
 c 
          orth1 = .true.
 c 
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call zcopy (n, resid, 1, workd(irj), 1)
@@ -611,7 +611,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*r_{j}
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -689,7 +689,7 @@ c
          call zaxpy (j, one, workd(irj), 1, h(1,j), 1)
 c 
          orth2 = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call zcopy (n, resid, 1, workd(irj), 1)
@@ -713,7 +713,7 @@ c        | Back from reverse communicati
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if 
 c
@@ -791,7 +791,7 @@ c 
          rstart = .false.
          orth2  = .false.
 c 
-         call second (t5)
+         call secnd2 (t5)
          titref = titref + (t5 - t4)
 c 
 c        %------------------------------------%
@@ -800,7 +800,7 @@ c        %------------------------------
 c
          j = j + 1
          if (j .gt. k+np) then
-            call second (t1)
+            call secnd2 (t1)
             tcaitr = tcaitr + (t1 - t0)
             ido = 99
             do 110 i = max(1,k), k+np-1
diff -up ARPACK/SRC/zgetv0.f.sb ARPACK/SRC/zgetv0.f
--- ARPACK/SRC/zgetv0.f.sb	1999-04-08 00:46:45.000000000 +0200
+++ ARPACK/SRC/zgetv0.f	2007-10-24 02:50:57.000000000 +0200
@@ -211,7 +211,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mgetv0
 c 
          ierr   = 0
@@ -238,7 +238,7 @@ c        | Force the starting vector int
 c        | the generalized problem when B is possibly (singular).   |
 c        %----------------------------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nopx = nopx + 1
             ipntr(1) = 1
@@ -261,7 +261,7 @@ c     %---------------------------------
 c
       if (orth)  go to 40
 c 
-      call second (t3)
+      call secnd2 (t3)
       tmvopx = tmvopx + (t3 - t2)
 c 
 c     %------------------------------------------------------%
@@ -269,7 +269,7 @@ c     | Starting vector is now in the ra
 c     | Compute B-norm of starting vector.                   |
 c     %------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       first = .TRUE.
       if (bmat .eq. 'G') then
          nbx = nbx + 1
@@ -285,7 +285,7 @@ c 
    20 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -328,7 +328,7 @@ c     %---------------------------------
 c     | Compute the B-norm of the orthogonalized starting vector |
 c     %----------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       if (bmat .eq. 'G') then
          nbx = nbx + 1
          call zcopy (n, resid, 1, workd(n+1), 1)
@@ -343,7 +343,7 @@ c 
    40 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -401,7 +401,7 @@ c
       end if
       ido = 99
 c 
-      call second (t1)
+      call secnd2 (t1)
       tgetv0 = tgetv0 + (t1 - t0)
 c 
  9000 continue
diff -up ARPACK/SRC/zneigh.f.sb ARPACK/SRC/zneigh.f
--- ARPACK/SRC/zneigh.f.sb	1996-04-20 19:16:01.000000000 +0200
+++ ARPACK/SRC/zneigh.f	2007-10-24 02:50:57.000000000 +0200
@@ -171,7 +171,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mceigh
 c 
       if (msglvl .gt. 2) then
@@ -244,7 +244,7 @@ c
      &              '_neigh: Ritz estimates for the eigenvalues of H')
       end if
 c
-      call second(t1)
+      call secnd2(t1)
       tceigh = tceigh + (t1 - t0)
 c
  9000 continue
diff -up ARPACK/SRC/cnaupd.f.sb ARPACK/SRC/cnaupd.f
--- ARPACK/SRC/cnaupd.f.sb	2002-08-15 07:50:57.000000000 +0200
+++ ARPACK/SRC/cnaupd.f	2007-10-24 02:50:57.000000000 +0200
@@ -451,7 +451,7 @@ c        | & message level for debugging
 c        %-------------------------------%
 c
          call cstatn
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mcaupd
 c
 c        %----------------%
@@ -611,7 +611,7 @@ c
      &               '_naupd: Associated Ritz estimates')
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tcaupd = t1 - t0
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/cgetv0.f.sb ARPACK/SRC/cgetv0.f
--- ARPACK/SRC/cgetv0.f.sb	1999-04-08 00:46:44.000000000 +0200
+++ ARPACK/SRC/cgetv0.f	2007-10-24 02:50:57.000000000 +0200
@@ -211,7 +211,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mgetv0
 c 
          ierr   = 0
@@ -238,7 +238,7 @@ c        | Force the starting vector int
 c        | the generalized problem when B is possibly (singular).   |
 c        %----------------------------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nopx = nopx + 1
             ipntr(1) = 1
@@ -261,7 +261,7 @@ c     %---------------------------------
 c
       if (orth)  go to 40
 c 
-      call second (t3)
+      call secnd2 (t3)
       tmvopx = tmvopx + (t3 - t2)
 c 
 c     %------------------------------------------------------%
@@ -269,7 +269,7 @@ c     | Starting vector is now in the ra
 c     | Compute B-norm of starting vector.                   |
 c     %------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       first = .TRUE.
       if (bmat .eq. 'G') then
          nbx = nbx + 1
@@ -285,7 +285,7 @@ c 
    20 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -328,7 +328,7 @@ c     %---------------------------------
 c     | Compute the B-norm of the orthogonalized starting vector |
 c     %----------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       if (bmat .eq. 'G') then
          nbx = nbx + 1
          call ccopy (n, resid, 1, workd(n+1), 1)
@@ -343,7 +343,7 @@ c 
    40 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -401,7 +401,7 @@ c
       end if
       ido = 99
 c 
-      call second (t1)
+      call secnd2 (t1)
       tgetv0 = tgetv0 + (t1 - t0)
 c 
  9000 continue
diff -up ARPACK/SRC/sgetv0.f.sb ARPACK/SRC/sgetv0.f
--- ARPACK/SRC/sgetv0.f.sb	1999-04-08 00:42:46.000000000 +0200
+++ ARPACK/SRC/sgetv0.f	2007-10-24 02:50:57.000000000 +0200
@@ -214,7 +214,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mgetv0
 c 
          ierr   = 0
@@ -241,7 +241,7 @@ c        | Force the starting vector int
 c        | the generalized problem when B is possibly (singular).   |
 c        %----------------------------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nopx = nopx + 1
             ipntr(1) = 1
@@ -265,7 +265,7 @@ c
       if (orth)  go to 40
 c 
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
       end if
 c 
@@ -274,7 +274,7 @@ c     | Starting vector is now in the ra
 c     | Compute B-norm of starting vector.                   |
 c     %------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       first = .TRUE.
       if (bmat .eq. 'G') then
          nbx = nbx + 1
@@ -290,7 +290,7 @@ c 
    20 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -333,7 +333,7 @@ c     %---------------------------------
 c     | Compute the B-norm of the orthogonalized starting vector |
 c     %----------------------------------------------------------%
 c
-      call second (t2)
+      call secnd2 (t2)
       if (bmat .eq. 'G') then
          nbx = nbx + 1
          call scopy (n, resid, 1, workd(n+1), 1)
@@ -348,7 +348,7 @@ c 
    40 continue
 c
       if (bmat .eq. 'G') then
-         call second (t3)
+         call secnd2 (t3)
          tmvbx = tmvbx + (t3 - t2)
       end if
 c 
@@ -406,7 +406,7 @@ c
       end if
       ido = 99
 c 
-      call second (t1)
+      call secnd2 (t1)
       tgetv0 = tgetv0 + (t1 - t0)
 c 
  9000 continue
diff -up ARPACK/SRC/dnaupd.f.sb ARPACK/SRC/dnaupd.f
--- ARPACK/SRC/dnaupd.f.sb	2002-08-23 07:29:34.000000000 +0200
+++ ARPACK/SRC/dnaupd.f	2007-10-24 02:50:57.000000000 +0200
@@ -476,7 +476,7 @@ c        | & message level for debugging
 c        %-------------------------------%
 c
          call dstatn
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mnaupd
 c
 c        %----------------%
@@ -640,7 +640,7 @@ c
      &               '_naupd: Associated Ritz estimates')
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tnaupd = t1 - t0
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/cnaitr.f.sb ARPACK/SRC/cnaitr.f
--- ARPACK/SRC/cnaitr.f.sb	1996-08-27 18:12:56.000000000 +0200
+++ ARPACK/SRC/cnaitr.f	2007-10-24 02:50:57.000000000 +0200
@@ -326,7 +326,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mcaitr
 c 
 c        %------------------------------%
@@ -437,7 +437,7 @@ c              | which spans OP and exit
 c              %------------------------------------------------%
 c
                info = j - 1
-               call second (t1)
+               call secnd2 (t1)
                tcaitr = tcaitr + (t1 - t0)
                ido = 99
                go to 9000
@@ -477,7 +477,7 @@ c        %------------------------------
 c
          step3 = .true.
          nopx  = nopx + 1
-         call second (t2)
+         call secnd2 (t2)
          call ccopy (n, v(1,j), 1, workd(ivj), 1)
          ipntr(1) = ivj
          ipntr(2) = irj
@@ -497,7 +497,7 @@ c        | WORKD(IRJ:IRJ+N-1) := OP*v_{j
 c        | if step3 = .true.                |
 c        %----------------------------------%
 c
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
  
          step3 = .false.
@@ -513,7 +513,7 @@ c        | STEP 4:  Finish extending the
 c        |          factorization to length j.   |
 c        %---------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             step4 = .true.
@@ -538,7 +538,7 @@ c        | if step4 = .true.            
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -583,11 +583,11 @@ c
 c
          if (j .gt. 1) h(j,j-1) = cmplx(betaj, rzero)
 c
-         call second (t4)
+         call secnd2 (t4)
 c 
          orth1 = .true.
 c 
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call ccopy (n, resid, 1, workd(irj), 1)
@@ -611,7 +611,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*r_{j}
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -689,7 +689,7 @@ c
          call caxpy (j, one, workd(irj), 1, h(1,j), 1)
 c 
          orth2 = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call ccopy (n, resid, 1, workd(irj), 1)
@@ -713,7 +713,7 @@ c        | Back from reverse communicati
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if 
 c
@@ -791,7 +791,7 @@ c 
          rstart = .false.
          orth2  = .false.
 c 
-         call second (t5)
+         call secnd2 (t5)
          titref = titref + (t5 - t4)
 c 
 c        %------------------------------------%
@@ -800,7 +800,7 @@ c        %------------------------------
 c
          j = j + 1
          if (j .gt. k+np) then
-            call second (t1)
+            call secnd2 (t1)
             tcaitr = tcaitr + (t1 - t0)
             ido = 99
             do 110 i = max(1,k), k+np-1
diff -up ARPACK/SRC/dsaupd.f.sb ARPACK/SRC/dsaupd.f
--- ARPACK/SRC/dsaupd.f.sb	2001-04-11 00:52:40.000000000 +0200
+++ ARPACK/SRC/dsaupd.f	2007-10-24 02:50:57.000000000 +0200
@@ -478,7 +478,7 @@ c        | & message level for debugging
 c        %-------------------------------%
 c
          call dstats 
-         call second (t0)
+         call secnd2 (t0)
          msglvl = msaupd
 c
          ierr   = 0
@@ -638,7 +638,7 @@ c
      &               '_saupd: corresponding error bounds')
       end if 
 c
-      call second (t1)
+      call secnd2 (t1)
       tsaupd = t1 - t0
 c 
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/znaup2.f.sb ARPACK/SRC/znaup2.f
--- ARPACK/SRC/znaup2.f.sb	2000-06-01 22:28:53.000000000 +0200
+++ ARPACK/SRC/znaup2.f	2007-10-24 02:50:57.000000000 +0200
@@ -264,7 +264,7 @@ c     %-----------------------%
 c
       if (ido .eq. 0) then
 c 
-         call second (t0)
+         call secnd2 (t0)
 c 
          msglvl = mcaup2
 c 
@@ -724,7 +724,7 @@ c        | the first step of the next ca
 c        %---------------------------------------------%
 c
          cnorm = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call zcopy  (n, resid, 1, workd(n+1), 1)
@@ -749,7 +749,7 @@ c        | WORKD(1:N) := B*RESID        
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -788,7 +788,7 @@ c     %------------%
 c     | Error Exit |
 c     %------------%
 c
-      call second (t1)
+      call secnd2 (t1)
       tcaup2 = t1 - t0
 c     
  9000 continue
diff -up ARPACK/SRC/snaitr.f.sb ARPACK/SRC/snaitr.f
--- ARPACK/SRC/snaitr.f.sb	1996-08-27 18:09:01.000000000 +0200
+++ ARPACK/SRC/snaitr.f	2007-10-24 02:50:57.000000000 +0200
@@ -319,7 +319,7 @@ c        | Initialize timing statistics 
 c        | & message level for debugging |
 c        %-------------------------------%
 c
-         call second (t0)
+         call secnd2 (t0)
          msglvl = mnaitr
 c 
 c        %------------------------------%
@@ -430,7 +430,7 @@ c              | which spans OP and exit
 c              %------------------------------------------------%
 c
                info = j - 1
-               call second (t1)
+               call secnd2 (t1)
                tnaitr = tnaitr + (t1 - t0)
                ido = 99
                go to 9000
@@ -470,7 +470,7 @@ c        %------------------------------
 c
          step3 = .true.
          nopx  = nopx + 1
-         call second (t2)
+         call secnd2 (t2)
          call scopy (n, v(1,j), 1, workd(ivj), 1)
          ipntr(1) = ivj
          ipntr(2) = irj
@@ -490,7 +490,7 @@ c        | WORKD(IRJ:IRJ+N-1) := OP*v_{j
 c        | if step3 = .true.                |
 c        %----------------------------------%
 c
-         call second (t3)
+         call secnd2 (t3)
          tmvopx = tmvopx + (t3 - t2)
  
          step3 = .false.
@@ -506,7 +506,7 @@ c        | STEP 4:  Finish extending the
 c        |          factorization to length j.   |
 c        %---------------------------------------%
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             step4 = .true.
@@ -531,7 +531,7 @@ c        | if step4 = .true.            
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -576,11 +576,11 @@ c
 c
          if (j .gt. 1) h(j,j-1) = betaj
 c
-         call second (t4)
+         call secnd2 (t4)
 c 
          orth1 = .true.
 c
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call scopy (n, resid, 1, workd(irj), 1)
@@ -604,7 +604,7 @@ c        | WORKD(IPJ:IPJ+N-1) := B*r_{j}
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -681,7 +681,7 @@ c
          call saxpy (j, one, workd(irj), 1, h(1,j), 1)
 c 
          orth2 = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call scopy (n, resid, 1, workd(irj), 1)
@@ -705,7 +705,7 @@ c        | Back from reverse communicati
 c        %---------------------------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c
@@ -783,7 +783,7 @@ c 
          rstart = .false.
          orth2  = .false.
 c 
-         call second (t5)
+         call secnd2 (t5)
          titref = titref + (t5 - t4)
 c 
 c        %------------------------------------%
@@ -792,7 +792,7 @@ c        %------------------------------
 c
          j = j + 1
          if (j .gt. k+np) then
-            call second (t1)
+            call secnd2 (t1)
             tnaitr = tnaitr + (t1 - t0)
             ido = 99
             do 110 i = max(1,k), k+np-1
diff -up ARPACK/SRC/cnapps.f.sb ARPACK/SRC/cnapps.f
--- ARPACK/SRC/cnapps.f.sb	1998-05-20 16:45:03.000000000 +0200
+++ ARPACK/SRC/cnapps.f	2007-10-24 02:50:57.000000000 +0200
@@ -240,7 +240,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mcapps
 c 
       kplusp = kev + np 
@@ -495,7 +495,7 @@ c
       end if
 c
  9000 continue
-      call second (t1)
+      call secnd2 (t1)
       tcapps = tcapps + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/dnconv.f.sb ARPACK/SRC/dnconv.f
--- ARPACK/SRC/dnconv.f.sb	1996-04-20 18:27:05.000000000 +0200
+++ ARPACK/SRC/dnconv.f	2007-10-24 02:50:57.000000000 +0200
@@ -119,7 +119,7 @@ c     |                                 
 c     | for some appropriate choice of norm.                        |
 c     %-------------------------------------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
 c
 c     %---------------------------------%
 c     | Get machine dependent constant. |
@@ -134,7 +134,7 @@ c
          if (bounds(i) .le. tol*temp)   nconv = nconv + 1
    20 continue
 c 
-      call second (t1)
+      call secnd2 (t1)
       tnconv = tnconv + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/dngets.f.sb ARPACK/SRC/dngets.f
--- ARPACK/SRC/dngets.f.sb	1996-04-20 18:27:07.000000000 +0200
+++ ARPACK/SRC/dngets.f	2007-10-24 02:50:57.000000000 +0200
@@ -152,7 +152,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c 
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mngets
 c 
 c     %----------------------------------------------------%
@@ -208,7 +208,7 @@ c     
          call dsortc ( 'SR', .true., np, bounds, ritzr, ritzi )
       end if
 c     
-      call second (t1)
+      call secnd2 (t1)
       tngets = tngets + (t1 - t0)
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/ssconv.f.sb ARPACK/SRC/ssconv.f
--- ARPACK/SRC/ssconv.f.sb	1996-04-20 18:27:27.000000000 +0200
+++ ARPACK/SRC/ssconv.f	2007-10-24 02:50:57.000000000 +0200
@@ -106,7 +106,7 @@ c     %-----------------------%
 c     | Executable Statements |
 c     %-----------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
 c
       eps23 = slamch('Epsilon-Machine') 
       eps23 = eps23**(2.0E+0 / 3.0E+0)
@@ -126,7 +126,7 @@ c
 c
    10 continue
 c 
-      call second (t1)
+      call secnd2 (t1)
       tsconv = tsconv + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/ssapps.f.sb ARPACK/SRC/ssapps.f
--- ARPACK/SRC/ssapps.f.sb	1998-05-20 16:58:58.000000000 +0200
+++ ARPACK/SRC/ssapps.f	2007-10-24 02:50:57.000000000 +0200
@@ -213,7 +213,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = msapps
 c 
       kplusp = kev + np 
@@ -503,7 +503,7 @@ c
          end if
       end if
 c
-      call second (t1)
+      call secnd2 (t1)
       tsapps = tsapps + (t1 - t0)
 c 
  9000 continue 
diff -up ARPACK/SRC/ssaupd.f.sb ARPACK/SRC/ssaupd.f
--- ARPACK/SRC/ssaupd.f.sb	2001-04-11 00:52:40.000000000 +0200
+++ ARPACK/SRC/ssaupd.f	2007-10-24 02:50:57.000000000 +0200
@@ -478,7 +478,7 @@ c        | & message level for debugging
 c        %-------------------------------%
 c
          call sstats
-         call second (t0)
+         call secnd2 (t0)
          msglvl = msaupd
 c
          ierr   = 0
@@ -638,7 +638,7 @@ c
      &               '_saupd: corresponding error bounds')
       end if 
 c
-      call second (t1)
+      call secnd2 (t1)
       tsaupd = t1 - t0
 c 
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/snconv.f.sb ARPACK/SRC/snconv.f
--- ARPACK/SRC/snconv.f.sb	1996-04-20 18:27:21.000000000 +0200
+++ ARPACK/SRC/snconv.f	2007-10-24 02:50:57.000000000 +0200
@@ -119,7 +119,7 @@ c     |                                 
 c     | for some appropriate choice of norm.                        |
 c     %-------------------------------------------------------------%
 c
-      call second (t0)
+      call secnd2 (t0)
 c
 c     %---------------------------------%
 c     | Get machine dependent constant. |
@@ -134,7 +134,7 @@ c
          if (bounds(i) .le. tol*temp)   nconv = nconv + 1
    20 continue
 c 
-      call second (t1)
+      call secnd2 (t1)
       tnconv = tnconv + (t1 - t0)
 c 
       return
diff -up ARPACK/SRC/cnaup2.f.sb ARPACK/SRC/cnaup2.f
--- ARPACK/SRC/cnaup2.f.sb	2000-06-01 22:28:53.000000000 +0200
+++ ARPACK/SRC/cnaup2.f	2007-10-24 02:50:57.000000000 +0200
@@ -264,7 +264,7 @@ c     %-----------------------%
 c
       if (ido .eq. 0) then
 c 
-         call second (t0)
+         call secnd2 (t0)
 c 
          msglvl = mcaup2
 c 
@@ -724,7 +724,7 @@ c        | the first step of the next ca
 c        %---------------------------------------------%
 c
          cnorm = .true.
-         call second (t2)
+         call secnd2 (t2)
          if (bmat .eq. 'G') then
             nbx = nbx + 1
             call ccopy (n, resid, 1, workd(n+1), 1)
@@ -749,7 +749,7 @@ c        | WORKD(1:N) := B*RESID        
 c        %----------------------------------%
 c
          if (bmat .eq. 'G') then
-            call second (t3)
+            call secnd2 (t3)
             tmvbx = tmvbx + (t3 - t2)
          end if
 c 
@@ -788,7 +788,7 @@ c     %------------%
 c     | Error Exit |
 c     %------------%
 c
-      call second (t1)
+      call secnd2 (t1)
       tcaup2 = t1 - t0
 c     
  9000 continue
diff -up ARPACK/SRC/dseigt.f.sb ARPACK/SRC/dseigt.f
--- ARPACK/SRC/dseigt.f.sb	1996-08-27 07:29:04.000000000 +0200
+++ ARPACK/SRC/dseigt.f	2007-10-24 02:50:57.000000000 +0200
@@ -138,7 +138,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------% 
 c
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mseigt
 c
       if (msglvl .gt. 0) then
@@ -168,7 +168,7 @@ c
          bounds(k) = rnorm*abs(bounds(k))
    30 continue
 c 
-      call second (t1)
+      call secnd2 (t1)
       tseigt = tseigt + (t1 - t0)
 c
  9000 continue
diff -up ARPACK/SRC/sngets.f.sb ARPACK/SRC/sngets.f
--- ARPACK/SRC/sngets.f.sb	1996-04-20 18:27:24.000000000 +0200
+++ ARPACK/SRC/sngets.f	2007-10-24 02:50:57.000000000 +0200
@@ -152,7 +152,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c 
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mngets
 c 
 c     %----------------------------------------------------%
@@ -208,7 +208,7 @@ c     
          call ssortc ( 'SR', .true., np, bounds, ritzr, ritzi )
       end if
 c     
-      call second (t1)
+      call secnd2 (t1)
       tngets = tngets + (t1 - t0)
 c
       if (msglvl .gt. 0) then
diff -up ARPACK/SRC/cngets.f.sb ARPACK/SRC/cngets.f
--- ARPACK/SRC/cngets.f.sb	1996-04-20 19:15:56.000000000 +0200
+++ ARPACK/SRC/cngets.f	2007-10-24 02:50:57.000000000 +0200
@@ -137,7 +137,7 @@ c     | Initialize timing statistics  |
 c     | & message level for debugging |
 c     %-------------------------------%
 c 
-      call second (t0)
+      call secnd2 (t0)
       msglvl = mcgets
 c 
       call csortc (which, .true., kev+np, ritz, bounds)
@@ -157,7 +157,7 @@ c     
 c
       end if
 c     
-      call second (t1)
+      call secnd2 (t1)
       tcgets = tcgets + (t1 - t0)
 c
       if (msglvl .gt. 0) then