File:  [local] / rpl / lapack / lapack / zhetri_3.f
Revision 1.5: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:25 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 ZHETRI_3
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZHETRI_3 + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhetri_3.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhetri_3.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetri_3.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZHETRI_3( UPLO, N, A, LDA, E, IPIV, WORK, LWORK,
   22: *                            INFO )
   23: *
   24: *       .. Scalar Arguments ..
   25: *       CHARACTER          UPLO
   26: *       INTEGER            INFO, LDA, LWORK, N
   27: *       ..
   28: *       .. Array Arguments ..
   29: *       INTEGER            IPIV( * )
   30: *       COMPLEX*16         A( LDA, * ), E( * ), WORK( * )
   31: *       ..
   32: *
   33: *
   34: *> \par Purpose:
   35: *  =============
   36: *>
   37: *> \verbatim
   38: *> ZHETRI_3 computes the inverse of a complex Hermitian indefinite
   39: *> matrix A using the factorization computed by ZHETRF_RK or ZHETRF_BK:
   40: *>
   41: *>     A = P*U*D*(U**H)*(P**T) or A = P*L*D*(L**H)*(P**T),
   42: *>
   43: *> where U (or L) is unit upper (or lower) triangular matrix,
   44: *> U**H (or L**H) is the conjugate of U (or L), P is a permutation
   45: *> matrix, P**T is the transpose of P, and D is Hermitian and block
   46: *> diagonal with 1-by-1 and 2-by-2 diagonal blocks.
   47: *>
   48: *> ZHETRI_3 sets the leading dimension of the workspace  before calling
   49: *> ZHETRI_3X that actually computes the inverse.  This is the blocked
   50: *> version of the algorithm, calling Level 3 BLAS.
   51: *> \endverbatim
   52: *
   53: *  Arguments:
   54: *  ==========
   55: *
   56: *> \param[in] UPLO
   57: *> \verbatim
   58: *>          UPLO is CHARACTER*1
   59: *>          Specifies whether the details of the factorization are
   60: *>          stored as an upper or lower triangular matrix.
   61: *>          = 'U':  Upper triangle of A is stored;
   62: *>          = 'L':  Lower triangle of A is stored.
   63: *> \endverbatim
   64: *>
   65: *> \param[in] N
   66: *> \verbatim
   67: *>          N is INTEGER
   68: *>          The order of the matrix A.  N >= 0.
   69: *> \endverbatim
   70: *>
   71: *> \param[in,out] A
   72: *> \verbatim
   73: *>          A is COMPLEX*16 array, dimension (LDA,N)
   74: *>          On entry, diagonal of the block diagonal matrix D and
   75: *>          factors U or L as computed by ZHETRF_RK and ZHETRF_BK:
   76: *>            a) ONLY diagonal elements of the Hermitian block diagonal
   77: *>               matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
   78: *>               (superdiagonal (or subdiagonal) elements of D
   79: *>                should be provided on entry in array E), and
   80: *>            b) If UPLO = 'U': factor U in the superdiagonal part of A.
   81: *>               If UPLO = 'L': factor L in the subdiagonal part of A.
   82: *>
   83: *>          On exit, if INFO = 0, the Hermitian inverse of the original
   84: *>          matrix.
   85: *>             If UPLO = 'U': the upper triangular part of the inverse
   86: *>             is formed and the part of A below the diagonal is not
   87: *>             referenced;
   88: *>             If UPLO = 'L': the lower triangular part of the inverse
   89: *>             is formed and the part of A above the diagonal is not
   90: *>             referenced.
   91: *> \endverbatim
   92: *>
   93: *> \param[in] LDA
   94: *> \verbatim
   95: *>          LDA is INTEGER
   96: *>          The leading dimension of the array A.  LDA >= max(1,N).
   97: *> \endverbatim
   98: *>
   99: *> \param[in] E
  100: *> \verbatim
  101: *>          E is COMPLEX*16 array, dimension (N)
  102: *>          On entry, contains the superdiagonal (or subdiagonal)
  103: *>          elements of the Hermitian block diagonal matrix D
  104: *>          with 1-by-1 or 2-by-2 diagonal blocks, where
  105: *>          If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not referenced;
  106: *>          If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
  107: *>
  108: *>          NOTE: For 1-by-1 diagonal block D(k), where
  109: *>          1 <= k <= N, the element E(k) is not referenced in both
  110: *>          UPLO = 'U' or UPLO = 'L' cases.
  111: *> \endverbatim
  112: *>
  113: *> \param[in] IPIV
  114: *> \verbatim
  115: *>          IPIV is INTEGER array, dimension (N)
  116: *>          Details of the interchanges and the block structure of D
  117: *>          as determined by ZHETRF_RK or ZHETRF_BK.
  118: *> \endverbatim
  119: *>
  120: *> \param[out] WORK
  121: *> \verbatim
  122: *>          WORK is COMPLEX*16 array, dimension (N+NB+1)*(NB+3).
  123: *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
  124: *> \endverbatim
  125: *>
  126: *> \param[in] LWORK
  127: *> \verbatim
  128: *>          LWORK is INTEGER
  129: *>          The length of WORK. LWORK >= (N+NB+1)*(NB+3).
  130: *>
  131: *>          If LDWORK = -1, then a workspace query is assumed;
  132: *>          the routine only calculates the optimal size of the optimal
  133: *>          size of the WORK array, returns this value as the first
  134: *>          entry of the WORK array, and no error message related to
  135: *>          LWORK is issued by XERBLA.
  136: *> \endverbatim
  137: *>
  138: *> \param[out] INFO
  139: *> \verbatim
  140: *>          INFO is INTEGER
  141: *>          = 0: successful exit
  142: *>          < 0: if INFO = -i, the i-th argument had an illegal value
  143: *>          > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
  144: *>               inverse could not be computed.
  145: *> \endverbatim
  146: *
  147: *  Authors:
  148: *  ========
  149: *
  150: *> \author Univ. of Tennessee
  151: *> \author Univ. of California Berkeley
  152: *> \author Univ. of Colorado Denver
  153: *> \author NAG Ltd.
  154: *
  155: *> \ingroup complex16HEcomputational
  156: *
  157: *> \par Contributors:
  158: *  ==================
  159: *> \verbatim
  160: *>
  161: *>  November 2017,  Igor Kozachenko,
  162: *>                  Computer Science Division,
  163: *>                  University of California, Berkeley
  164: *>
  165: *> \endverbatim
  166: *
  167: *  =====================================================================
  168:       SUBROUTINE ZHETRI_3( UPLO, N, A, LDA, E, IPIV, WORK, LWORK,
  169:      $                     INFO )
  170: *
  171: *  -- LAPACK computational routine --
  172: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  173: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  174: *
  175: *     .. Scalar Arguments ..
  176:       CHARACTER          UPLO
  177:       INTEGER            INFO, LDA, LWORK, N
  178: *     ..
  179: *     .. Array Arguments ..
  180:       INTEGER            IPIV( * )
  181:       COMPLEX*16         A( LDA, * ), E( * ), WORK( * )
  182: *     ..
  183: *
  184: *  =====================================================================
  185: *
  186: *     .. Local Scalars ..
  187:       LOGICAL            UPPER, LQUERY
  188:       INTEGER            LWKOPT, NB
  189: *     ..
  190: *     .. External Functions ..
  191:       LOGICAL            LSAME
  192:       INTEGER            ILAENV
  193:       EXTERNAL           LSAME, ILAENV
  194: *     ..
  195: *     .. External Subroutines ..
  196:       EXTERNAL           ZHETRI_3X, XERBLA
  197: *     ..
  198: *     .. Intrinsic Functions ..
  199:       INTRINSIC          MAX
  200: *     ..
  201: *     .. Executable Statements ..
  202: *
  203: *     Test the input parameters.
  204: *
  205:       INFO = 0
  206:       UPPER = LSAME( UPLO, 'U' )
  207:       LQUERY = ( LWORK.EQ.-1 )
  208: *
  209: *     Determine the block size
  210: *
  211:       NB = MAX( 1, ILAENV( 1, 'ZHETRI_3', UPLO, N, -1, -1, -1 ) )
  212:       LWKOPT = ( N+NB+1 ) * ( NB+3 )
  213: *
  214:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  215:          INFO = -1
  216:       ELSE IF( N.LT.0 ) THEN
  217:          INFO = -2
  218:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  219:          INFO = -4
  220:       ELSE IF ( LWORK .LT. LWKOPT .AND. .NOT.LQUERY ) THEN
  221:          INFO = -8
  222:       END IF
  223: *
  224:       IF( INFO.NE.0 ) THEN
  225:          CALL XERBLA( 'ZHETRI_3', -INFO )
  226:          RETURN
  227:       ELSE IF( LQUERY ) THEN
  228:          WORK( 1 ) = LWKOPT
  229:          RETURN
  230:       END IF
  231: *
  232: *     Quick return if possible
  233: *
  234:       IF( N.EQ.0 )
  235:      $   RETURN
  236: *
  237:       CALL ZHETRI_3X( UPLO, N, A, LDA, E, IPIV, WORK, NB, INFO )
  238: *
  239:       WORK( 1 ) = LWKOPT
  240: *
  241:       RETURN
  242: *
  243: *     End of ZHETRI_3
  244: *
  245:       END

CVSweb interface <joel.bertrand@systella.fr>