File:  [local] / rpl / lapack / lapack / zlatrd.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:32 2023 UTC (8 months, 3 weeks ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Première mise à jour de lapack et blas.

    1: *> \brief \b ZLATRD reduces the first nb rows and columns of a symmetric/Hermitian matrix A to real tridiagonal form by an unitary similarity transformation.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZLATRD + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlatrd.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlatrd.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatrd.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZLATRD( UPLO, N, NB, A, LDA, E, TAU, W, LDW )
   22: *
   23: *       .. Scalar Arguments ..
   24: *       CHARACTER          UPLO
   25: *       INTEGER            LDA, LDW, N, NB
   26: *       ..
   27: *       .. Array Arguments ..
   28: *       DOUBLE PRECISION   E( * )
   29: *       COMPLEX*16         A( LDA, * ), TAU( * ), W( LDW, * )
   30: *       ..
   31: *
   32: *
   33: *> \par Purpose:
   34: *  =============
   35: *>
   36: *> \verbatim
   37: *>
   38: *> ZLATRD reduces NB rows and columns of a complex Hermitian matrix A to
   39: *> Hermitian tridiagonal form by a unitary similarity
   40: *> transformation Q**H * A * Q, and returns the matrices V and W which are
   41: *> needed to apply the transformation to the unreduced part of A.
   42: *>
   43: *> If UPLO = 'U', ZLATRD reduces the last NB rows and columns of a
   44: *> matrix, of which the upper triangle is supplied;
   45: *> if UPLO = 'L', ZLATRD reduces the first NB rows and columns of a
   46: *> matrix, of which the lower triangle is supplied.
   47: *>
   48: *> This is an auxiliary routine called by ZHETRD.
   49: *> \endverbatim
   50: *
   51: *  Arguments:
   52: *  ==========
   53: *
   54: *> \param[in] UPLO
   55: *> \verbatim
   56: *>          UPLO is CHARACTER*1
   57: *>          Specifies whether the upper or lower triangular part of the
   58: *>          Hermitian matrix A is stored:
   59: *>          = 'U': Upper triangular
   60: *>          = 'L': Lower triangular
   61: *> \endverbatim
   62: *>
   63: *> \param[in] N
   64: *> \verbatim
   65: *>          N is INTEGER
   66: *>          The order of the matrix A.
   67: *> \endverbatim
   68: *>
   69: *> \param[in] NB
   70: *> \verbatim
   71: *>          NB is INTEGER
   72: *>          The number of rows and columns to be reduced.
   73: *> \endverbatim
   74: *>
   75: *> \param[in,out] A
   76: *> \verbatim
   77: *>          A is COMPLEX*16 array, dimension (LDA,N)
   78: *>          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
   79: *>          n-by-n upper triangular part of A contains the upper
   80: *>          triangular part of the matrix A, and the strictly lower
   81: *>          triangular part of A is not referenced.  If UPLO = 'L', the
   82: *>          leading n-by-n lower triangular part of A contains the lower
   83: *>          triangular part of the matrix A, and the strictly upper
   84: *>          triangular part of A is not referenced.
   85: *>          On exit:
   86: *>          if UPLO = 'U', the last NB columns have been reduced to
   87: *>            tridiagonal form, with the diagonal elements overwriting
   88: *>            the diagonal elements of A; the elements above the diagonal
   89: *>            with the array TAU, represent the unitary matrix Q as a
   90: *>            product of elementary reflectors;
   91: *>          if UPLO = 'L', the first NB columns have been reduced to
   92: *>            tridiagonal form, with the diagonal elements overwriting
   93: *>            the diagonal elements of A; the elements below the diagonal
   94: *>            with the array TAU, represent the  unitary matrix Q as a
   95: *>            product of elementary reflectors.
   96: *>          See Further Details.
   97: *> \endverbatim
   98: *>
   99: *> \param[in] LDA
  100: *> \verbatim
  101: *>          LDA is INTEGER
  102: *>          The leading dimension of the array A.  LDA >= max(1,N).
  103: *> \endverbatim
  104: *>
  105: *> \param[out] E
  106: *> \verbatim
  107: *>          E is DOUBLE PRECISION array, dimension (N-1)
  108: *>          If UPLO = 'U', E(n-nb:n-1) contains the superdiagonal
  109: *>          elements of the last NB columns of the reduced matrix;
  110: *>          if UPLO = 'L', E(1:nb) contains the subdiagonal elements of
  111: *>          the first NB columns of the reduced matrix.
  112: *> \endverbatim
  113: *>
  114: *> \param[out] TAU
  115: *> \verbatim
  116: *>          TAU is COMPLEX*16 array, dimension (N-1)
  117: *>          The scalar factors of the elementary reflectors, stored in
  118: *>          TAU(n-nb:n-1) if UPLO = 'U', and in TAU(1:nb) if UPLO = 'L'.
  119: *>          See Further Details.
  120: *> \endverbatim
  121: *>
  122: *> \param[out] W
  123: *> \verbatim
  124: *>          W is COMPLEX*16 array, dimension (LDW,NB)
  125: *>          The n-by-nb matrix W required to update the unreduced part
  126: *>          of A.
  127: *> \endverbatim
  128: *>
  129: *> \param[in] LDW
  130: *> \verbatim
  131: *>          LDW is INTEGER
  132: *>          The leading dimension of the array W. LDW >= max(1,N).
  133: *> \endverbatim
  134: *
  135: *  Authors:
  136: *  ========
  137: *
  138: *> \author Univ. of Tennessee
  139: *> \author Univ. of California Berkeley
  140: *> \author Univ. of Colorado Denver
  141: *> \author NAG Ltd.
  142: *
  143: *> \ingroup complex16OTHERauxiliary
  144: *
  145: *> \par Further Details:
  146: *  =====================
  147: *>
  148: *> \verbatim
  149: *>
  150: *>  If UPLO = 'U', the matrix Q is represented as a product of elementary
  151: *>  reflectors
  152: *>
  153: *>     Q = H(n) H(n-1) . . . H(n-nb+1).
  154: *>
  155: *>  Each H(i) has the form
  156: *>
  157: *>     H(i) = I - tau * v * v**H
  158: *>
  159: *>  where tau is a complex scalar, and v is a complex vector with
  160: *>  v(i:n) = 0 and v(i-1) = 1; v(1:i-1) is stored on exit in A(1:i-1,i),
  161: *>  and tau in TAU(i-1).
  162: *>
  163: *>  If UPLO = 'L', the matrix Q is represented as a product of elementary
  164: *>  reflectors
  165: *>
  166: *>     Q = H(1) H(2) . . . H(nb).
  167: *>
  168: *>  Each H(i) has the form
  169: *>
  170: *>     H(i) = I - tau * v * v**H
  171: *>
  172: *>  where tau is a complex scalar, and v is a complex vector with
  173: *>  v(1:i) = 0 and v(i+1) = 1; v(i+1:n) is stored on exit in A(i+1:n,i),
  174: *>  and tau in TAU(i).
  175: *>
  176: *>  The elements of the vectors v together form the n-by-nb matrix V
  177: *>  which is needed, with W, to apply the transformation to the unreduced
  178: *>  part of the matrix, using a Hermitian rank-2k update of the form:
  179: *>  A := A - V*W**H - W*V**H.
  180: *>
  181: *>  The contents of A on exit are illustrated by the following examples
  182: *>  with n = 5 and nb = 2:
  183: *>
  184: *>  if UPLO = 'U':                       if UPLO = 'L':
  185: *>
  186: *>    (  a   a   a   v4  v5 )              (  d                  )
  187: *>    (      a   a   v4  v5 )              (  1   d              )
  188: *>    (          a   1   v5 )              (  v1  1   a          )
  189: *>    (              d   1  )              (  v1  v2  a   a      )
  190: *>    (                  d  )              (  v1  v2  a   a   a  )
  191: *>
  192: *>  where d denotes a diagonal element of the reduced matrix, a denotes
  193: *>  an element of the original matrix that is unchanged, and vi denotes
  194: *>  an element of the vector defining H(i).
  195: *> \endverbatim
  196: *>
  197: *  =====================================================================
  198:       SUBROUTINE ZLATRD( UPLO, N, NB, A, LDA, E, TAU, W, LDW )
  199: *
  200: *  -- LAPACK auxiliary routine --
  201: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  202: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  203: *
  204: *     .. Scalar Arguments ..
  205:       CHARACTER          UPLO
  206:       INTEGER            LDA, LDW, N, NB
  207: *     ..
  208: *     .. Array Arguments ..
  209:       DOUBLE PRECISION   E( * )
  210:       COMPLEX*16         A( LDA, * ), TAU( * ), W( LDW, * )
  211: *     ..
  212: *
  213: *  =====================================================================
  214: *
  215: *     .. Parameters ..
  216:       COMPLEX*16         ZERO, ONE, HALF
  217:       PARAMETER          ( ZERO = ( 0.0D+0, 0.0D+0 ),
  218:      $                   ONE = ( 1.0D+0, 0.0D+0 ),
  219:      $                   HALF = ( 0.5D+0, 0.0D+0 ) )
  220: *     ..
  221: *     .. Local Scalars ..
  222:       INTEGER            I, IW
  223:       COMPLEX*16         ALPHA
  224: *     ..
  225: *     .. External Subroutines ..
  226:       EXTERNAL           ZAXPY, ZGEMV, ZHEMV, ZLACGV, ZLARFG, ZSCAL
  227: *     ..
  228: *     .. External Functions ..
  229:       LOGICAL            LSAME
  230:       COMPLEX*16         ZDOTC
  231:       EXTERNAL           LSAME, ZDOTC
  232: *     ..
  233: *     .. Intrinsic Functions ..
  234:       INTRINSIC          DBLE, MIN
  235: *     ..
  236: *     .. Executable Statements ..
  237: *
  238: *     Quick return if possible
  239: *
  240:       IF( N.LE.0 )
  241:      $   RETURN
  242: *
  243:       IF( LSAME( UPLO, 'U' ) ) THEN
  244: *
  245: *        Reduce last NB columns of upper triangle
  246: *
  247:          DO 10 I = N, N - NB + 1, -1
  248:             IW = I - N + NB
  249:             IF( I.LT.N ) THEN
  250: *
  251: *              Update A(1:i,i)
  252: *
  253:                A( I, I ) = DBLE( A( I, I ) )
  254:                CALL ZLACGV( N-I, W( I, IW+1 ), LDW )
  255:                CALL ZGEMV( 'No transpose', I, N-I, -ONE, A( 1, I+1 ),
  256:      $                     LDA, W( I, IW+1 ), LDW, ONE, A( 1, I ), 1 )
  257:                CALL ZLACGV( N-I, W( I, IW+1 ), LDW )
  258:                CALL ZLACGV( N-I, A( I, I+1 ), LDA )
  259:                CALL ZGEMV( 'No transpose', I, N-I, -ONE, W( 1, IW+1 ),
  260:      $                     LDW, A( I, I+1 ), LDA, ONE, A( 1, I ), 1 )
  261:                CALL ZLACGV( N-I, A( I, I+1 ), LDA )
  262:                A( I, I ) = DBLE( A( I, I ) )
  263:             END IF
  264:             IF( I.GT.1 ) THEN
  265: *
  266: *              Generate elementary reflector H(i) to annihilate
  267: *              A(1:i-2,i)
  268: *
  269:                ALPHA = A( I-1, I )
  270:                CALL ZLARFG( I-1, ALPHA, A( 1, I ), 1, TAU( I-1 ) )
  271:                E( I-1 ) = DBLE( ALPHA )
  272:                A( I-1, I ) = ONE
  273: *
  274: *              Compute W(1:i-1,i)
  275: *
  276:                CALL ZHEMV( 'Upper', I-1, ONE, A, LDA, A( 1, I ), 1,
  277:      $                     ZERO, W( 1, IW ), 1 )
  278:                IF( I.LT.N ) THEN
  279:                   CALL ZGEMV( 'Conjugate transpose', I-1, N-I, ONE,
  280:      $                        W( 1, IW+1 ), LDW, A( 1, I ), 1, ZERO,
  281:      $                        W( I+1, IW ), 1 )
  282:                   CALL ZGEMV( 'No transpose', I-1, N-I, -ONE,
  283:      $                        A( 1, I+1 ), LDA, W( I+1, IW ), 1, ONE,
  284:      $                        W( 1, IW ), 1 )
  285:                   CALL ZGEMV( 'Conjugate transpose', I-1, N-I, ONE,
  286:      $                        A( 1, I+1 ), LDA, A( 1, I ), 1, ZERO,
  287:      $                        W( I+1, IW ), 1 )
  288:                   CALL ZGEMV( 'No transpose', I-1, N-I, -ONE,
  289:      $                        W( 1, IW+1 ), LDW, W( I+1, IW ), 1, ONE,
  290:      $                        W( 1, IW ), 1 )
  291:                END IF
  292:                CALL ZSCAL( I-1, TAU( I-1 ), W( 1, IW ), 1 )
  293:                ALPHA = -HALF*TAU( I-1 )*ZDOTC( I-1, W( 1, IW ), 1,
  294:      $                 A( 1, I ), 1 )
  295:                CALL ZAXPY( I-1, ALPHA, A( 1, I ), 1, W( 1, IW ), 1 )
  296:             END IF
  297: *
  298:    10    CONTINUE
  299:       ELSE
  300: *
  301: *        Reduce first NB columns of lower triangle
  302: *
  303:          DO 20 I = 1, NB
  304: *
  305: *           Update A(i:n,i)
  306: *
  307:             A( I, I ) = DBLE( A( I, I ) )
  308:             CALL ZLACGV( I-1, W( I, 1 ), LDW )
  309:             CALL ZGEMV( 'No transpose', N-I+1, I-1, -ONE, A( I, 1 ),
  310:      $                  LDA, W( I, 1 ), LDW, ONE, A( I, I ), 1 )
  311:             CALL ZLACGV( I-1, W( I, 1 ), LDW )
  312:             CALL ZLACGV( I-1, A( I, 1 ), LDA )
  313:             CALL ZGEMV( 'No transpose', N-I+1, I-1, -ONE, W( I, 1 ),
  314:      $                  LDW, A( I, 1 ), LDA, ONE, A( I, I ), 1 )
  315:             CALL ZLACGV( I-1, A( I, 1 ), LDA )
  316:             A( I, I ) = DBLE( A( I, I ) )
  317:             IF( I.LT.N ) THEN
  318: *
  319: *              Generate elementary reflector H(i) to annihilate
  320: *              A(i+2:n,i)
  321: *
  322:                ALPHA = A( I+1, I )
  323:                CALL ZLARFG( N-I, ALPHA, A( MIN( I+2, N ), I ), 1,
  324:      $                      TAU( I ) )
  325:                E( I ) = DBLE( ALPHA )
  326:                A( I+1, I ) = ONE
  327: *
  328: *              Compute W(i+1:n,i)
  329: *
  330:                CALL ZHEMV( 'Lower', N-I, ONE, A( I+1, I+1 ), LDA,
  331:      $                     A( I+1, I ), 1, ZERO, W( I+1, I ), 1 )
  332:                CALL ZGEMV( 'Conjugate transpose', N-I, I-1, ONE,
  333:      $                     W( I+1, 1 ), LDW, A( I+1, I ), 1, ZERO,
  334:      $                     W( 1, I ), 1 )
  335:                CALL ZGEMV( 'No transpose', N-I, I-1, -ONE, A( I+1, 1 ),
  336:      $                     LDA, W( 1, I ), 1, ONE, W( I+1, I ), 1 )
  337:                CALL ZGEMV( 'Conjugate transpose', N-I, I-1, ONE,
  338:      $                     A( I+1, 1 ), LDA, A( I+1, I ), 1, ZERO,
  339:      $                     W( 1, I ), 1 )
  340:                CALL ZGEMV( 'No transpose', N-I, I-1, -ONE, W( I+1, 1 ),
  341:      $                     LDW, W( 1, I ), 1, ONE, W( I+1, I ), 1 )
  342:                CALL ZSCAL( N-I, TAU( I ), W( I+1, I ), 1 )
  343:                ALPHA = -HALF*TAU( I )*ZDOTC( N-I, W( I+1, I ), 1,
  344:      $                 A( I+1, I ), 1 )
  345:                CALL ZAXPY( N-I, ALPHA, A( I+1, I ), 1, W( I+1, I ), 1 )
  346:             END IF
  347: *
  348:    20    CONTINUE
  349:       END IF
  350: *
  351:       RETURN
  352: *
  353: *     End of ZLATRD
  354: *
  355:       END

CVSweb interface <joel.bertrand@systella.fr>