LAPACK 3.3.0

zhetri.f

Go to the documentation of this file.
00001       SUBROUTINE ZHETRI( UPLO, N, A, LDA, IPIV, WORK, INFO )
00002 *
00003 *  -- LAPACK routine (version 3.2) --
00004 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00005 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00006 *     November 2006
00007 *
00008 *     .. Scalar Arguments ..
00009       CHARACTER          UPLO
00010       INTEGER            INFO, LDA, N
00011 *     ..
00012 *     .. Array Arguments ..
00013       INTEGER            IPIV( * )
00014       COMPLEX*16         A( LDA, * ), WORK( * )
00015 *     ..
00016 *
00017 *  Purpose
00018 *  =======
00019 *
00020 *  ZHETRI computes the inverse of a complex Hermitian indefinite matrix
00021 *  A using the factorization A = U*D*U**H or A = L*D*L**H computed by
00022 *  ZHETRF.
00023 *
00024 *  Arguments
00025 *  =========
00026 *
00027 *  UPLO    (input) CHARACTER*1
00028 *          Specifies whether the details of the factorization are stored
00029 *          as an upper or lower triangular matrix.
00030 *          = 'U':  Upper triangular, form is A = U*D*U**H;
00031 *          = 'L':  Lower triangular, form is A = L*D*L**H.
00032 *
00033 *  N       (input) INTEGER
00034 *          The order of the matrix A.  N >= 0.
00035 *
00036 *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
00037 *          On entry, the block diagonal matrix D and the multipliers
00038 *          used to obtain the factor U or L as computed by ZHETRF.
00039 *
00040 *          On exit, if INFO = 0, the (Hermitian) inverse of the original
00041 *          matrix.  If UPLO = 'U', the upper triangular part of the
00042 *          inverse is formed and the part of A below the diagonal is not
00043 *          referenced; if UPLO = 'L' the lower triangular part of the
00044 *          inverse is formed and the part of A above the diagonal is
00045 *          not referenced.
00046 *
00047 *  LDA     (input) INTEGER
00048 *          The leading dimension of the array A.  LDA >= max(1,N).
00049 *
00050 *  IPIV    (input) INTEGER array, dimension (N)
00051 *          Details of the interchanges and the block structure of D
00052 *          as determined by ZHETRF.
00053 *
00054 *  WORK    (workspace) COMPLEX*16 array, dimension (N)
00055 *
00056 *  INFO    (output) INTEGER
00057 *          = 0: successful exit
00058 *          < 0: if INFO = -i, the i-th argument had an illegal value
00059 *          > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
00060 *               inverse could not be computed.
00061 *
00062 *  =====================================================================
00063 *
00064 *     .. Parameters ..
00065       DOUBLE PRECISION   ONE
00066       COMPLEX*16         CONE, ZERO
00067       PARAMETER          ( ONE = 1.0D+0, CONE = ( 1.0D+0, 0.0D+0 ),
00068      $                   ZERO = ( 0.0D+0, 0.0D+0 ) )
00069 *     ..
00070 *     .. Local Scalars ..
00071       LOGICAL            UPPER
00072       INTEGER            J, K, KP, KSTEP
00073       DOUBLE PRECISION   AK, AKP1, D, T
00074       COMPLEX*16         AKKP1, TEMP
00075 *     ..
00076 *     .. External Functions ..
00077       LOGICAL            LSAME
00078       COMPLEX*16         ZDOTC
00079       EXTERNAL           LSAME, ZDOTC
00080 *     ..
00081 *     .. External Subroutines ..
00082       EXTERNAL           XERBLA, ZCOPY, ZHEMV, ZSWAP
00083 *     ..
00084 *     .. Intrinsic Functions ..
00085       INTRINSIC          ABS, DBLE, DCONJG, MAX
00086 *     ..
00087 *     .. Executable Statements ..
00088 *
00089 *     Test the input parameters.
00090 *
00091       INFO = 0
00092       UPPER = LSAME( UPLO, 'U' )
00093       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
00094          INFO = -1
00095       ELSE IF( N.LT.0 ) THEN
00096          INFO = -2
00097       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
00098          INFO = -4
00099       END IF
00100       IF( INFO.NE.0 ) THEN
00101          CALL XERBLA( 'ZHETRI', -INFO )
00102          RETURN
00103       END IF
00104 *
00105 *     Quick return if possible
00106 *
00107       IF( N.EQ.0 )
00108      $   RETURN
00109 *
00110 *     Check that the diagonal matrix D is nonsingular.
00111 *
00112       IF( UPPER ) THEN
00113 *
00114 *        Upper triangular storage: examine D from bottom to top
00115 *
00116          DO 10 INFO = N, 1, -1
00117             IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
00118      $         RETURN
00119    10    CONTINUE
00120       ELSE
00121 *
00122 *        Lower triangular storage: examine D from top to bottom.
00123 *
00124          DO 20 INFO = 1, N
00125             IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
00126      $         RETURN
00127    20    CONTINUE
00128       END IF
00129       INFO = 0
00130 *
00131       IF( UPPER ) THEN
00132 *
00133 *        Compute inv(A) from the factorization A = U*D*U'.
00134 *
00135 *        K is the main loop index, increasing from 1 to N in steps of
00136 *        1 or 2, depending on the size of the diagonal blocks.
00137 *
00138          K = 1
00139    30    CONTINUE
00140 *
00141 *        If K > N, exit from loop.
00142 *
00143          IF( K.GT.N )
00144      $      GO TO 50
00145 *
00146          IF( IPIV( K ).GT.0 ) THEN
00147 *
00148 *           1 x 1 diagonal block
00149 *
00150 *           Invert the diagonal block.
00151 *
00152             A( K, K ) = ONE / DBLE( A( K, K ) )
00153 *
00154 *           Compute column K of the inverse.
00155 *
00156             IF( K.GT.1 ) THEN
00157                CALL ZCOPY( K-1, A( 1, K ), 1, WORK, 1 )
00158                CALL ZHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, ZERO,
00159      $                     A( 1, K ), 1 )
00160                A( K, K ) = A( K, K ) - DBLE( ZDOTC( K-1, WORK, 1, A( 1,
00161      $                     K ), 1 ) )
00162             END IF
00163             KSTEP = 1
00164          ELSE
00165 *
00166 *           2 x 2 diagonal block
00167 *
00168 *           Invert the diagonal block.
00169 *
00170             T = ABS( A( K, K+1 ) )
00171             AK = DBLE( A( K, K ) ) / T
00172             AKP1 = DBLE( A( K+1, K+1 ) ) / T
00173             AKKP1 = A( K, K+1 ) / T
00174             D = T*( AK*AKP1-ONE )
00175             A( K, K ) = AKP1 / D
00176             A( K+1, K+1 ) = AK / D
00177             A( K, K+1 ) = -AKKP1 / D
00178 *
00179 *           Compute columns K and K+1 of the inverse.
00180 *
00181             IF( K.GT.1 ) THEN
00182                CALL ZCOPY( K-1, A( 1, K ), 1, WORK, 1 )
00183                CALL ZHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, ZERO,
00184      $                     A( 1, K ), 1 )
00185                A( K, K ) = A( K, K ) - DBLE( ZDOTC( K-1, WORK, 1, A( 1,
00186      $                     K ), 1 ) )
00187                A( K, K+1 ) = A( K, K+1 ) -
00188      $                       ZDOTC( K-1, A( 1, K ), 1, A( 1, K+1 ), 1 )
00189                CALL ZCOPY( K-1, A( 1, K+1 ), 1, WORK, 1 )
00190                CALL ZHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, ZERO,
00191      $                     A( 1, K+1 ), 1 )
00192                A( K+1, K+1 ) = A( K+1, K+1 ) -
00193      $                         DBLE( ZDOTC( K-1, WORK, 1, A( 1, K+1 ),
00194      $                         1 ) )
00195             END IF
00196             KSTEP = 2
00197          END IF
00198 *
00199          KP = ABS( IPIV( K ) )
00200          IF( KP.NE.K ) THEN
00201 *
00202 *           Interchange rows and columns K and KP in the leading
00203 *           submatrix A(1:k+1,1:k+1)
00204 *
00205             CALL ZSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
00206             DO 40 J = KP + 1, K - 1
00207                TEMP = DCONJG( A( J, K ) )
00208                A( J, K ) = DCONJG( A( KP, J ) )
00209                A( KP, J ) = TEMP
00210    40       CONTINUE
00211             A( KP, K ) = DCONJG( A( KP, K ) )
00212             TEMP = A( K, K )
00213             A( K, K ) = A( KP, KP )
00214             A( KP, KP ) = TEMP
00215             IF( KSTEP.EQ.2 ) THEN
00216                TEMP = A( K, K+1 )
00217                A( K, K+1 ) = A( KP, K+1 )
00218                A( KP, K+1 ) = TEMP
00219             END IF
00220          END IF
00221 *
00222          K = K + KSTEP
00223          GO TO 30
00224    50    CONTINUE
00225 *
00226       ELSE
00227 *
00228 *        Compute inv(A) from the factorization A = L*D*L'.
00229 *
00230 *        K is the main loop index, increasing from 1 to N in steps of
00231 *        1 or 2, depending on the size of the diagonal blocks.
00232 *
00233          K = N
00234    60    CONTINUE
00235 *
00236 *        If K < 1, exit from loop.
00237 *
00238          IF( K.LT.1 )
00239      $      GO TO 80
00240 *
00241          IF( IPIV( K ).GT.0 ) THEN
00242 *
00243 *           1 x 1 diagonal block
00244 *
00245 *           Invert the diagonal block.
00246 *
00247             A( K, K ) = ONE / DBLE( A( K, K ) )
00248 *
00249 *           Compute column K of the inverse.
00250 *
00251             IF( K.LT.N ) THEN
00252                CALL ZCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
00253                CALL ZHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
00254      $                     1, ZERO, A( K+1, K ), 1 )
00255                A( K, K ) = A( K, K ) - DBLE( ZDOTC( N-K, WORK, 1,
00256      $                     A( K+1, K ), 1 ) )
00257             END IF
00258             KSTEP = 1
00259          ELSE
00260 *
00261 *           2 x 2 diagonal block
00262 *
00263 *           Invert the diagonal block.
00264 *
00265             T = ABS( A( K, K-1 ) )
00266             AK = DBLE( A( K-1, K-1 ) ) / T
00267             AKP1 = DBLE( A( K, K ) ) / T
00268             AKKP1 = A( K, K-1 ) / T
00269             D = T*( AK*AKP1-ONE )
00270             A( K-1, K-1 ) = AKP1 / D
00271             A( K, K ) = AK / D
00272             A( K, K-1 ) = -AKKP1 / D
00273 *
00274 *           Compute columns K-1 and K of the inverse.
00275 *
00276             IF( K.LT.N ) THEN
00277                CALL ZCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
00278                CALL ZHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
00279      $                     1, ZERO, A( K+1, K ), 1 )
00280                A( K, K ) = A( K, K ) - DBLE( ZDOTC( N-K, WORK, 1,
00281      $                     A( K+1, K ), 1 ) )
00282                A( K, K-1 ) = A( K, K-1 ) -
00283      $                       ZDOTC( N-K, A( K+1, K ), 1, A( K+1, K-1 ),
00284      $                       1 )
00285                CALL ZCOPY( N-K, A( K+1, K-1 ), 1, WORK, 1 )
00286                CALL ZHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
00287      $                     1, ZERO, A( K+1, K-1 ), 1 )
00288                A( K-1, K-1 ) = A( K-1, K-1 ) -
00289      $                         DBLE( ZDOTC( N-K, WORK, 1, A( K+1, K-1 ),
00290      $                         1 ) )
00291             END IF
00292             KSTEP = 2
00293          END IF
00294 *
00295          KP = ABS( IPIV( K ) )
00296          IF( KP.NE.K ) THEN
00297 *
00298 *           Interchange rows and columns K and KP in the trailing
00299 *           submatrix A(k-1:n,k-1:n)
00300 *
00301             IF( KP.LT.N )
00302      $         CALL ZSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
00303             DO 70 J = K + 1, KP - 1
00304                TEMP = DCONJG( A( J, K ) )
00305                A( J, K ) = DCONJG( A( KP, J ) )
00306                A( KP, J ) = TEMP
00307    70       CONTINUE
00308             A( KP, K ) = DCONJG( A( KP, K ) )
00309             TEMP = A( K, K )
00310             A( K, K ) = A( KP, KP )
00311             A( KP, KP ) = TEMP
00312             IF( KSTEP.EQ.2 ) THEN
00313                TEMP = A( K, K-1 )
00314                A( K, K-1 ) = A( KP, K-1 )
00315                A( KP, K-1 ) = TEMP
00316             END IF
00317          END IF
00318 *
00319          K = K - KSTEP
00320          GO TO 60
00321    80    CONTINUE
00322       END IF
00323 *
00324       RETURN
00325 *
00326 *     End of ZHETRI
00327 *
00328       END
 All Files Functions