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

version 1.7, 2010/12/21 13:53:49 version 1.8, 2011/07/22 07:38:17
Line 1 Line 1
       SUBROUTINE ZLAHRD( N, K, NB, A, LDA, TAU, T, LDT, Y, LDY )        SUBROUTINE ZLAHRD( N, K, NB, A, LDA, TAU, T, LDT, Y, LDY )
 *  *
 *  -- LAPACK auxiliary routine (version 3.2) --  *  -- LAPACK auxiliary 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 ..
       INTEGER            K, LDA, LDT, LDY, N, NB        INTEGER            K, LDA, LDT, LDY, N, NB
Line 19 Line 19
 *  ZLAHRD reduces the first NB columns of a complex general n-by-(n-k+1)  *  ZLAHRD reduces the first NB columns of a complex general n-by-(n-k+1)
 *  matrix A so that elements below the k-th subdiagonal are zero. The  *  matrix A so that elements below the k-th subdiagonal are zero. The
 *  reduction is performed by a unitary similarity transformation  *  reduction is performed by a unitary similarity transformation
 *  Q' * A * Q. The routine returns the matrices V and T which determine  *  Q**H * A * Q. The routine returns the matrices V and T which determine
 *  Q as a block reflector I - V*T*V', and also the matrix Y = A * V * T.  *  Q as a block reflector I - V*T*V**H, and also the matrix Y = A * V * T.
 *  *
 *  This is an OBSOLETE auxiliary routine.   *  This is an OBSOLETE auxiliary routine. 
 *  This routine will be 'deprecated' in a  future release.  *  This routine will be 'deprecated' in a  future release.
Line 76 Line 76
 *  *
 *  Each H(i) has the form  *  Each H(i) has the form
 *  *
 *     H(i) = I - tau * v * v'  *     H(i) = I - tau * v * v**H
 *  *
 *  where tau is a complex scalar, and v is a complex vector with  *  where tau is a complex scalar, and v is a complex vector with
 *  v(1:i+k-1) = 0, v(i+k) = 1; v(i+k+1:n) is stored on exit in  *  v(1:i+k-1) = 0, v(i+k) = 1; v(i+k+1:n) is stored on exit in
Line 85 Line 85
 *  The elements of the vectors v together form the (n-k+1)-by-nb matrix  *  The elements of the vectors v together form the (n-k+1)-by-nb matrix
 *  V which is needed, with T and Y, to apply the transformation to the  *  V which is needed, with T and Y, to apply the transformation to the
 *  unreduced part of the matrix, using an update of the form:  *  unreduced part of the matrix, using an update of the form:
 *  A := (I - V*T*V') * (A - Y*V').  *  A := (I - V*T*V**H) * (A - Y*V**H).
 *  *
 *  The contents of A on exit are illustrated by the following example  *  The contents of A on exit are illustrated by the following example
 *  with n = 7, k = 3 and nb = 2:  *  with n = 7, k = 3 and nb = 2:
Line 132 Line 132
 *  *
 *           Update A(1:n,i)  *           Update A(1:n,i)
 *  *
 *           Compute i-th column of A - Y * V'  *           Compute i-th column of A - Y * V**H
 *  *
             CALL ZLACGV( I-1, A( K+I-1, 1 ), LDA )              CALL ZLACGV( I-1, A( K+I-1, 1 ), LDA )
             CALL ZGEMV( 'No transpose', N, I-1, -ONE, Y, LDY,              CALL ZGEMV( 'No transpose', N, I-1, -ONE, Y, LDY,
      $                  A( K+I-1, 1 ), LDA, ONE, A( 1, I ), 1 )       $                  A( K+I-1, 1 ), LDA, ONE, A( 1, I ), 1 )
             CALL ZLACGV( I-1, A( K+I-1, 1 ), LDA )              CALL ZLACGV( I-1, A( K+I-1, 1 ), LDA )
 *  *
 *           Apply I - V * T' * V' to this column (call it b) from the  *           Apply I - V * T**H * V**H to this column (call it b) from the
 *           left, using the last column of T as workspace  *           left, using the last column of T as workspace
 *  *
 *           Let  V = ( V1 )   and   b = ( b1 )   (first I-1 rows)  *           Let  V = ( V1 )   and   b = ( b1 )   (first I-1 rows)
Line 147 Line 147
 *  *
 *           where V1 is unit lower triangular  *           where V1 is unit lower triangular
 *  *
 *           w := V1' * b1  *           w := V1**H * b1
 *  *
             CALL ZCOPY( I-1, A( K+1, I ), 1, T( 1, NB ), 1 )              CALL ZCOPY( I-1, A( K+1, I ), 1, T( 1, NB ), 1 )
             CALL ZTRMV( 'Lower', 'Conjugate transpose', 'Unit', I-1,              CALL ZTRMV( 'Lower', 'Conjugate transpose', 'Unit', I-1,
      $                  A( K+1, 1 ), LDA, T( 1, NB ), 1 )       $                  A( K+1, 1 ), LDA, T( 1, NB ), 1 )
 *  *
 *           w := w + V2'*b2  *           w := w + V2**H *b2
 *  *
             CALL ZGEMV( 'Conjugate transpose', N-K-I+1, I-1, ONE,              CALL ZGEMV( 'Conjugate transpose', N-K-I+1, I-1, ONE,
      $                  A( K+I, 1 ), LDA, A( K+I, I ), 1, ONE,       $                  A( K+I, 1 ), LDA, A( K+I, I ), 1, ONE,
      $                  T( 1, NB ), 1 )       $                  T( 1, NB ), 1 )
 *  *
 *           w := T'*w  *           w := T**H *w
 *  *
             CALL ZTRMV( 'Upper', 'Conjugate transpose', 'Non-unit', I-1,              CALL ZTRMV( 'Upper', 'Conjugate transpose', 'Non-unit', I-1,
      $                  T, LDT, T( 1, NB ), 1 )       $                  T, LDT, T( 1, NB ), 1 )

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


CVSweb interface <joel.bertrand@systella.fr>