3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SPOTRI + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spotri.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spotri.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spotri.f">
21 * SUBROUTINE SPOTRI( UPLO, N, A, LDA, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, N
27 * .. Array Arguments ..
37 *> SPOTRI computes the inverse of a real symmetric positive definite
38 *> matrix A using the Cholesky factorization A = U**T*U or A = L*L**T
39 *> computed by SPOTRF.
47 *> UPLO is CHARACTER*1
48 *> = 'U': Upper triangle of A is stored;
49 *> = 'L': Lower triangle of A is stored.
55 *> The order of the matrix A. N >= 0.
60 *> A is REAL array, dimension (LDA,N)
61 *> On entry, the triangular factor U or L from the Cholesky
62 *> factorization A = U**T*U or A = L*L**T, as computed by
64 *> On exit, the upper or lower triangle of the (symmetric)
65 *> inverse of A, overwriting the input factor U or L.
71 *> The leading dimension of the array A. LDA >= max(1,N).
77 *> = 0: successful exit
78 *> < 0: if INFO = -i, the i-th argument had an illegal value
79 *> > 0: if INFO = i, the (i,i) element of the factor U or L is
80 *> zero, and the inverse could not be computed.
86 *> \author Univ. of Tennessee
87 *> \author Univ. of California Berkeley
88 *> \author Univ. of Colorado Denver
91 *> \date November 2011
93 *> \ingroup realPOcomputational
95 * =====================================================================
96 SUBROUTINE SPOTRI( UPLO, N, A, LDA, INFO )
98 * -- LAPACK computational routine (version 3.4.0) --
99 * -- LAPACK is a software package provided by Univ. of Tennessee, --
100 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
103 * .. Scalar Arguments ..
107 * .. Array Arguments ..
111 * =====================================================================
113 * .. External Functions ..
117 * .. External Subroutines ..
118 EXTERNAL SLAUUM, STRTRI, XERBLA
120 * .. Intrinsic Functions ..
123 * .. Executable Statements ..
125 * Test the input parameters.
128 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
130 ELSE IF( N.LT.0 ) THEN
132 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
136 CALL XERBLA( 'SPOTRI', -INFO )
140 * Quick return if possible
145 * Invert the triangular Cholesky factor U or L.
147 CALL STRTRI( UPLO, 'Non-unit', N, A, LDA, INFO )
151 * Form inv(U) * inv(U)**T or inv(L)**T * inv(L).
153 CALL SLAUUM( UPLO, N, A, LDA, INFO )