LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 minor of order i is not
                positive definite, and the factorization could not be
                completed.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2015

Definition at line 108 of file spotrf2.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: