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

◆ dpotf2()

subroutine dpotf2 ( character  uplo,
integer  n,
double precision, dimension( lda, * )  a,
integer  lda,
integer  info 
)

DPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblocked algorithm).

Download DPOTF2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DPOTF2 computes the Cholesky factorization of a real symmetric
 positive definite matrix A.

 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 unblocked version of the algorithm, calling Level 2 BLAS.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the upper or lower triangular part of the
          symmetric matrix A is stored.
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]A
          A is DOUBLE PRECISION 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 = -k, the k-th argument had an illegal value
          > 0: if INFO = k, the leading principal minor of order k
               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 108 of file dpotf2.f.

109*
110* -- LAPACK computational routine --
111* -- LAPACK is a software package provided by Univ. of Tennessee, --
112* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
113*
114* .. Scalar Arguments ..
115 CHARACTER UPLO
116 INTEGER INFO, LDA, N
117* ..
118* .. Array Arguments ..
119 DOUBLE PRECISION A( LDA, * )
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 DOUBLE PRECISION ONE, ZERO
126 parameter( one = 1.0d+0, zero = 0.0d+0 )
127* ..
128* .. Local Scalars ..
129 LOGICAL UPPER
130 INTEGER J
131 DOUBLE PRECISION AJJ
132* ..
133* .. External Functions ..
134 LOGICAL LSAME, DISNAN
135 DOUBLE PRECISION DDOT
136 EXTERNAL lsame, ddot, disnan
137* ..
138* .. External Subroutines ..
139 EXTERNAL dgemv, dscal, xerbla
140* ..
141* .. Intrinsic Functions ..
142 INTRINSIC max, sqrt
143* ..
144* .. Executable Statements ..
145*
146* Test the input parameters.
147*
148 info = 0
149 upper = lsame( uplo, 'U' )
150 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
151 info = -1
152 ELSE IF( n.LT.0 ) THEN
153 info = -2
154 ELSE IF( lda.LT.max( 1, n ) ) THEN
155 info = -4
156 END IF
157 IF( info.NE.0 ) THEN
158 CALL xerbla( 'DPOTF2', -info )
159 RETURN
160 END IF
161*
162* Quick return if possible
163*
164 IF( n.EQ.0 )
165 $ RETURN
166*
167 IF( upper ) THEN
168*
169* Compute the Cholesky factorization A = U**T *U.
170*
171 DO 10 j = 1, n
172*
173* Compute U(J,J) and test for non-positive-definiteness.
174*
175 ajj = a( j, j ) - ddot( j-1, a( 1, j ), 1, a( 1, j ), 1 )
176 IF( ajj.LE.zero.OR.disnan( ajj ) ) THEN
177 a( j, j ) = ajj
178 GO TO 30
179 END IF
180 ajj = sqrt( ajj )
181 a( j, j ) = ajj
182*
183* Compute elements J+1:N of row J.
184*
185 IF( j.LT.n ) THEN
186 CALL dgemv( 'Transpose', j-1, n-j, -one, a( 1, j+1 ),
187 $ lda, a( 1, j ), 1, one, a( j, j+1 ), lda )
188 CALL dscal( n-j, one / ajj, a( j, j+1 ), lda )
189 END IF
190 10 CONTINUE
191 ELSE
192*
193* Compute the Cholesky factorization A = L*L**T.
194*
195 DO 20 j = 1, n
196*
197* Compute L(J,J) and test for non-positive-definiteness.
198*
199 ajj = a( j, j ) - ddot( j-1, a( j, 1 ), lda, a( j, 1 ),
200 $ lda )
201 IF( ajj.LE.zero.OR.disnan( ajj ) ) THEN
202 a( j, j ) = ajj
203 GO TO 30
204 END IF
205 ajj = sqrt( ajj )
206 a( j, j ) = ajj
207*
208* Compute elements J+1:N of column J.
209*
210 IF( j.LT.n ) THEN
211 CALL dgemv( 'No transpose', n-j, j-1, -one, a( j+1, 1 ),
212 $ lda, a( j, 1 ), lda, one, a( j+1, j ), 1 )
213 CALL dscal( n-j, one / ajj, a( j+1, j ), 1 )
214 END IF
215 20 CONTINUE
216 END IF
217 GO TO 40
218*
219 30 CONTINUE
220 info = j
221*
222 40 CONTINUE
223 RETURN
224*
225* End of DPOTF2
226*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function ddot(n, dx, incx, dy, incy)
DDOT
Definition ddot.f:82
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
Here is the call graph for this function:
Here is the caller graph for this function: