LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ spotrf2()

recursive subroutine spotrf2 ( character uplo,
integer n,
real, dimension( lda, * ) a,
integer lda,
integer info )

SPOTRF2

Purpose:
!>
!> SPOTRF2 computes the Cholesky factorization of a real symmetric
!> positive definite matrix A using the recursive algorithm.
!>
!> The factorization has the form
!>    A = U**T * U,  if UPLO = 'U', or
!>    A = L  * L**T,  if UPLO = 'L',
!> where U is an upper triangular matrix and L is lower triangular.
!>
!> This is the recursive version of the algorithm. It divides
!> the matrix into four submatrices:
!>
!>        [  A11 | A12  ]  where A11 is n1 by n1 and A22 is n2 by n2
!>    A = [ -----|----- ]  with n1 = n/2
!>        [  A21 | A22  ]       n2 = n-n1
!>
!> The subroutine calls itself to factor A11. Update and scale A21
!> or A12, update A22 then call itself to factor A22.
!>
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  Upper triangle of A is stored;
!>          = 'L':  Lower triangle of A is stored.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in,out]A
!>          A is REAL array, dimension (LDA,N)
!>          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
!>          N-by-N upper triangular part of A contains the upper
!>          triangular part of the matrix A, and the strictly lower
!>          triangular part of A is not referenced.  If UPLO = 'L', the
!>          leading N-by-N lower triangular part of A contains the lower
!>          triangular part of the matrix A, and the strictly upper
!>          triangular part of A is not referenced.
!>
!>          On exit, if INFO = 0, the factor U or L from the Cholesky
!>          factorization A = U**T*U or A = L*L**T.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!>          > 0:  if INFO = i, the leading principal minor of order i
!>                is not positive, and the factorization could not be
!>                completed.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 105 of file spotrf2.f.

106*
107* -- LAPACK computational routine --
108* -- LAPACK is a software package provided by Univ. of Tennessee, --
109* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
110*
111* .. Scalar Arguments ..
112 CHARACTER UPLO
113 INTEGER INFO, LDA, N
114* ..
115* .. Array Arguments ..
116 REAL A( LDA, * )
117* ..
118*
119* =====================================================================
120*
121* .. Parameters ..
122 REAL ONE, ZERO
123 parameter( one = 1.0e+0, zero=0.0e+0 )
124* ..
125* .. Local Scalars ..
126 LOGICAL UPPER
127 INTEGER N1, N2, IINFO
128* ..
129* .. External Functions ..
130 LOGICAL LSAME, SISNAN
131 EXTERNAL lsame, sisnan
132* ..
133* .. External Subroutines ..
134 EXTERNAL ssyrk, strsm, xerbla
135* ..
136* .. Intrinsic Functions ..
137 INTRINSIC max, sqrt
138* ..
139* .. Executable Statements ..
140*
141* Test the input parameters
142*
143 info = 0
144 upper = lsame( uplo, 'U' )
145 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
146 info = -1
147 ELSE IF( n.LT.0 ) THEN
148 info = -2
149 ELSE IF( lda.LT.max( 1, n ) ) THEN
150 info = -4
151 END IF
152 IF( info.NE.0 ) THEN
153 CALL xerbla( 'SPOTRF2', -info )
154 RETURN
155 END IF
156*
157* Quick return if possible
158*
159 IF( n.EQ.0 )
160 $ RETURN
161*
162* N=1 case
163*
164 IF( n.EQ.1 ) THEN
165*
166* Test for non-positive-definiteness
167*
168 IF( a( 1, 1 ).LE.zero.OR.sisnan( a( 1, 1 ) ) ) THEN
169 info = 1
170 RETURN
171 END IF
172*
173* Factor
174*
175 a( 1, 1 ) = sqrt( a( 1, 1 ) )
176*
177* Use recursive code
178*
179 ELSE
180 n1 = n/2
181 n2 = n-n1
182*
183* Factor A11
184*
185 CALL spotrf2( uplo, n1, a( 1, 1 ), lda, iinfo )
186 IF ( iinfo.NE.0 ) THEN
187 info = iinfo
188 RETURN
189 END IF
190*
191* Compute the Cholesky factorization A = U**T*U
192*
193 IF( upper ) THEN
194*
195* Update and scale A12
196*
197 CALL strsm( 'L', 'U', 'T', 'N', n1, n2, one,
198 $ a( 1, 1 ), lda, a( 1, n1+1 ), lda )
199*
200* Update and factor A22
201*
202 CALL ssyrk( uplo, 'T', n2, n1, -one, a( 1, n1+1 ), lda,
203 $ one, a( n1+1, n1+1 ), lda )
204 CALL spotrf2( uplo, n2, a( n1+1, n1+1 ), lda, iinfo )
205 IF ( iinfo.NE.0 ) THEN
206 info = iinfo + n1
207 RETURN
208 END IF
209*
210* Compute the Cholesky factorization A = L*L**T
211*
212 ELSE
213*
214* Update and scale A21
215*
216 CALL strsm( 'R', 'L', 'T', 'N', n2, n1, one,
217 $ a( 1, 1 ), lda, a( n1+1, 1 ), lda )
218*
219* Update and factor A22
220*
221 CALL ssyrk( uplo, 'N', n2, n1, -one, a( n1+1, 1 ), lda,
222 $ one, a( n1+1, n1+1 ), lda )
223 CALL spotrf2( uplo, n2, a( n1+1, n1+1 ), lda, iinfo )
224 IF ( iinfo.NE.0 ) THEN
225 info = iinfo + n1
226 RETURN
227 END IF
228 END IF
229 END IF
230 RETURN
231*
232* End of SPOTRF2
233*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
SSYRK
Definition ssyrk.f:169
logical function sisnan(sin)
SISNAN tests input for NaN.
Definition sisnan.f:57
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
recursive subroutine spotrf2(uplo, n, a, lda, info)
SPOTRF2
Definition spotrf2.f:106
subroutine strsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRSM
Definition strsm.f:181
Here is the call graph for this function:
Here is the caller graph for this function: