Diff for /rpl/lapack/lapack/dtrevc.f between versions 1.7 and 1.8

version 1.7, 2010/12/21 13:53:40 version 1.8, 2011/07/22 07:38:13
Line 1 Line 1
       SUBROUTINE DTREVC( SIDE, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR,        SUBROUTINE DTREVC( SIDE, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR,
      $                   LDVR, MM, M, WORK, INFO )       $                   LDVR, MM, M, WORK, INFO )
 *  *
 *  -- LAPACK routine (version 3.2) --  *  -- LAPACK routine (version 3.3.1) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     November 2006  *  -- April 2011                                                      --
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       CHARACTER          HOWMNY, SIDE        CHARACTER          HOWMNY, SIDE
Line 27 Line 27
 *  The right eigenvector x and the left eigenvector y of T corresponding  *  The right eigenvector x and the left eigenvector y of T corresponding
 *  to an eigenvalue w are defined by:  *  to an eigenvalue w are defined by:
 *    *  
 *     T*x = w*x,     (y**H)*T = w*(y**H)  *     T*x = w*x,     (y**T)*T = w*(y**T)
 *    *  
 *  where y**H denotes the conjugate transpose of y.  *  where y**T denotes the transpose of y.
 *  The eigenvalues are not input to this routine, but are read directly  *  The eigenvalues are not input to this routine, but are read directly
 *  from the diagonal blocks of T.  *  from the diagonal blocks of T.
 *    *  
Line 651 Line 651
   160          CONTINUE    160          CONTINUE
 *  *
 *              Solve the quasi-triangular system:  *              Solve the quasi-triangular system:
 *                 (T(KI+1:N,KI+1:N) - WR)'*X = SCALE*WORK  *                 (T(KI+1:N,KI+1:N) - WR)**T*X = SCALE*WORK
 *  *
                VMAX = ONE                 VMAX = ONE
                VCRIT = BIGNUM                 VCRIT = BIGNUM
Line 688 Line 688
      $                             DDOT( J-KI-1, T( KI+1, J ), 1,       $                             DDOT( J-KI-1, T( KI+1, J ), 1,
      $                             WORK( KI+1+N ), 1 )       $                             WORK( KI+1+N ), 1 )
 *  *
 *                    Solve (T(J,J)-WR)'*X = WORK  *                    Solve (T(J,J)-WR)**T*X = WORK
 *  *
                      CALL DLALN2( .FALSE., 1, 1, SMIN, ONE, T( J, J ),                       CALL DLALN2( .FALSE., 1, 1, SMIN, ONE, T( J, J ),
      $                            LDT, ONE, ONE, WORK( J+N ), N, WR,       $                            LDT, ONE, ONE, WORK( J+N ), N, WR,
Line 726 Line 726
      $                               WORK( KI+1+N ), 1 )       $                               WORK( KI+1+N ), 1 )
 *  *
 *                    Solve  *                    Solve
 *                      [T(J,J)-WR   T(J,J+1)     ]'* X = SCALE*( WORK1 )  *                      [T(J,J)-WR   T(J,J+1)     ]**T * X = SCALE*( WORK1 )
 *                      [T(J+1,J)    T(J+1,J+1)-WR]             ( WORK2 )  *                      [T(J+1,J)    T(J+1,J+1)-WR]                ( WORK2 )
 *  *
                      CALL DLALN2( .TRUE., 2, 1, SMIN, ONE, T( J, J ),                       CALL DLALN2( .TRUE., 2, 1, SMIN, ONE, T( J, J ),
      $                            LDT, ONE, ONE, WORK( J+N ), N, WR,       $                            LDT, ONE, ONE, WORK( J+N ), N, WR,
Line 778 Line 778
 *              Complex left eigenvector.  *              Complex left eigenvector.
 *  *
 *               Initial solve:  *               Initial solve:
 *                 ((T(KI,KI)    T(KI,KI+1) )' - (WR - I* WI))*X = 0.  *                 ((T(KI,KI)    T(KI,KI+1) )**T - (WR - I* WI))*X = 0.
 *                 ((T(KI+1,KI) T(KI+1,KI+1))                )  *                 ((T(KI+1,KI) T(KI+1,KI+1))                )
 *  *
                IF( ABS( T( KI, KI+1 ) ).GE.ABS( T( KI+1, KI ) ) ) THEN                 IF( ABS( T( KI, KI+1 ) ).GE.ABS( T( KI+1, KI ) ) ) THEN
Line 891 Line 891
      $                                WORK( KI+2+N2 ), 1 )       $                                WORK( KI+2+N2 ), 1 )
 *  *
 *                    Solve 2-by-2 complex linear equation  *                    Solve 2-by-2 complex linear equation
 *                      ([T(j,j)   T(j,j+1)  ]'-(wr-i*wi)*I)*X = SCALE*B  *                      ([T(j,j)   T(j,j+1)  ]**T-(wr-i*wi)*I)*X = SCALE*B
 *                      ([T(j+1,j) T(j+1,j+1)]             )  *                      ([T(j+1,j) T(j+1,j+1)]               )
 *  *
                      CALL DLALN2( .TRUE., 2, 2, SMIN, ONE, T( J, J ),                       CALL DLALN2( .TRUE., 2, 2, SMIN, ONE, T( J, J ),
      $                            LDT, ONE, ONE, WORK( J+N ), N, WR,       $                            LDT, ONE, ONE, WORK( J+N ), N, WR,

Removed from v.1.7  
changed lines
  Added in v.1.8


CVSweb interface <joel.bertrand@systella.fr>