File:  [local] / rpl / lapack / lapack / zlaev2.f
Revision 1.18: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:28 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 ZLAEV2 computes the eigenvalues and eigenvectors of a 2-by-2 symmetric/Hermitian matrix.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZLAEV2 + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlaev2.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlaev2.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaev2.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
   22: *
   23: *       .. Scalar Arguments ..
   24: *       DOUBLE PRECISION   CS1, RT1, RT2
   25: *       COMPLEX*16         A, B, C, SN1
   26: *       ..
   27: *
   28: *
   29: *> \par Purpose:
   30: *  =============
   31: *>
   32: *> \verbatim
   33: *>
   34: *> ZLAEV2 computes the eigendecomposition of a 2-by-2 Hermitian matrix
   35: *>    [  A         B  ]
   36: *>    [  CONJG(B)  C  ].
   37: *> On return, RT1 is the eigenvalue of larger absolute value, RT2 is the
   38: *> eigenvalue of smaller absolute value, and (CS1,SN1) is the unit right
   39: *> eigenvector for RT1, giving the decomposition
   40: *>
   41: *> [ CS1  CONJG(SN1) ] [    A     B ] [ CS1 -CONJG(SN1) ] = [ RT1  0  ]
   42: *> [-SN1     CS1     ] [ CONJG(B) C ] [ SN1     CS1     ]   [  0  RT2 ].
   43: *> \endverbatim
   44: *
   45: *  Arguments:
   46: *  ==========
   47: *
   48: *> \param[in] A
   49: *> \verbatim
   50: *>          A is COMPLEX*16
   51: *>         The (1,1) element of the 2-by-2 matrix.
   52: *> \endverbatim
   53: *>
   54: *> \param[in] B
   55: *> \verbatim
   56: *>          B is COMPLEX*16
   57: *>         The (1,2) element and the conjugate of the (2,1) element of
   58: *>         the 2-by-2 matrix.
   59: *> \endverbatim
   60: *>
   61: *> \param[in] C
   62: *> \verbatim
   63: *>          C is COMPLEX*16
   64: *>         The (2,2) element of the 2-by-2 matrix.
   65: *> \endverbatim
   66: *>
   67: *> \param[out] RT1
   68: *> \verbatim
   69: *>          RT1 is DOUBLE PRECISION
   70: *>         The eigenvalue of larger absolute value.
   71: *> \endverbatim
   72: *>
   73: *> \param[out] RT2
   74: *> \verbatim
   75: *>          RT2 is DOUBLE PRECISION
   76: *>         The eigenvalue of smaller absolute value.
   77: *> \endverbatim
   78: *>
   79: *> \param[out] CS1
   80: *> \verbatim
   81: *>          CS1 is DOUBLE PRECISION
   82: *> \endverbatim
   83: *>
   84: *> \param[out] SN1
   85: *> \verbatim
   86: *>          SN1 is COMPLEX*16
   87: *>         The vector (CS1, SN1) is a unit right eigenvector for RT1.
   88: *> \endverbatim
   89: *
   90: *  Authors:
   91: *  ========
   92: *
   93: *> \author Univ. of Tennessee
   94: *> \author Univ. of California Berkeley
   95: *> \author Univ. of Colorado Denver
   96: *> \author NAG Ltd.
   97: *
   98: *> \ingroup complex16OTHERauxiliary
   99: *
  100: *> \par Further Details:
  101: *  =====================
  102: *>
  103: *> \verbatim
  104: *>
  105: *>  RT1 is accurate to a few ulps barring over/underflow.
  106: *>
  107: *>  RT2 may be inaccurate if there is massive cancellation in the
  108: *>  determinant A*C-B*B; higher precision or correctly rounded or
  109: *>  correctly truncated arithmetic would be needed to compute RT2
  110: *>  accurately in all cases.
  111: *>
  112: *>  CS1 and SN1 are accurate to a few ulps barring over/underflow.
  113: *>
  114: *>  Overflow is possible only if RT1 is within a factor of 5 of overflow.
  115: *>  Underflow is harmless if the input data is 0 or exceeds
  116: *>     underflow_threshold / macheps.
  117: *> \endverbatim
  118: *>
  119: *  =====================================================================
  120:       SUBROUTINE ZLAEV2( A, B, C, RT1, RT2, CS1, SN1 )
  121: *
  122: *  -- LAPACK auxiliary routine --
  123: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  124: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  125: *
  126: *     .. Scalar Arguments ..
  127:       DOUBLE PRECISION   CS1, RT1, RT2
  128:       COMPLEX*16         A, B, C, SN1
  129: *     ..
  130: *
  131: * =====================================================================
  132: *
  133: *     .. Parameters ..
  134:       DOUBLE PRECISION   ZERO
  135:       PARAMETER          ( ZERO = 0.0D0 )
  136:       DOUBLE PRECISION   ONE
  137:       PARAMETER          ( ONE = 1.0D0 )
  138: *     ..
  139: *     .. Local Scalars ..
  140:       DOUBLE PRECISION   T
  141:       COMPLEX*16         W
  142: *     ..
  143: *     .. External Subroutines ..
  144:       EXTERNAL           DLAEV2
  145: *     ..
  146: *     .. Intrinsic Functions ..
  147:       INTRINSIC          ABS, DBLE, DCONJG
  148: *     ..
  149: *     .. Executable Statements ..
  150: *
  151:       IF( ABS( B ).EQ.ZERO ) THEN
  152:          W = ONE
  153:       ELSE
  154:          W = DCONJG( B ) / ABS( B )
  155:       END IF
  156:       CALL DLAEV2( DBLE( A ), ABS( B ), DBLE( C ), RT1, RT2, CS1, T )
  157:       SN1 = W*T
  158:       RETURN
  159: *
  160: *     End of ZLAEV2
  161: *
  162:       END

CVSweb interface <joel.bertrand@systella.fr>