KTH framework for Nek5000 toolboxes; testing version  0.0.1
dpotf2.f
Go to the documentation of this file.
1  SUBROUTINE dpotf2( UPLO, N, A, LDA, INFO )
2 *
3 * -- LAPACK routine (version 3.0) --
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
5 * Courant Institute, Argonne National Lab, and Rice University
6 * February 29, 1992
7 *
8 * .. Scalar Arguments ..
9  CHARACTER UPLO
10  INTEGER INFO, LDA, N
11 * ..
12 * .. Array Arguments ..
13  DOUBLE PRECISION A( LDA, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * DPOTF2 computes the Cholesky factorization of a real symmetric
20 * positive definite matrix A.
21 *
22 * The factorization has the form
23 * A = U' * U , if UPLO = 'U', or
24 * A = L * L', if UPLO = 'L',
25 * where U is an upper triangular matrix and L is lower triangular.
26 *
27 * This is the unblocked version of the algorithm, calling Level 2 BLAS.
28 *
29 * Arguments
30 * =========
31 *
32 * UPLO (input) CHARACTER*1
33 * Specifies whether the upper or lower triangular part of the
34 * symmetric matrix A is stored.
35 * = 'U': Upper triangular
36 * = 'L': Lower triangular
37 *
38 * N (input) INTEGER
39 * The order of the matrix A. N >= 0.
40 *
41 * A (input/output) DOUBLE PRECISION array, dimension (LDA,N)
42 * On entry, the symmetric matrix A. If UPLO = 'U', the leading
43 * n by n upper triangular part of A contains the upper
44 * triangular part of the matrix A, and the strictly lower
45 * triangular part of A is not referenced. If UPLO = 'L', the
46 * leading n by n lower triangular part of A contains the lower
47 * triangular part of the matrix A, and the strictly upper
48 * triangular part of A is not referenced.
49 *
50 * On exit, if INFO = 0, the factor U or L from the Cholesky
51 * factorization A = U'*U or A = L*L'.
52 *
53 * LDA (input) INTEGER
54 * The leading dimension of the array A. LDA >= max(1,N).
55 *
56 * INFO (output) INTEGER
57 * = 0: successful exit
58 * < 0: if INFO = -k, the k-th argument had an illegal value
59 * > 0: if INFO = k, the leading minor of order k is not
60 * positive definite, and the factorization could not be
61 * completed.
62 *
63 * =====================================================================
64 *
65 * .. Parameters ..
66  DOUBLE PRECISION ONE, ZERO
67  parameter( one = 1.0d+0, zero = 0.0d+0 )
68 * ..
69 * .. Local Scalars ..
70  LOGICAL UPPER
71  INTEGER J
72  DOUBLE PRECISION AJJ
73 * ..
74 * .. External Functions ..
75  LOGICAL LSAME
76  DOUBLE PRECISION DDOT
77  EXTERNAL lsame, ddot
78 * ..
79 * .. External Subroutines ..
80  EXTERNAL dgemv, dscal, xerbla
81 * ..
82 * .. Intrinsic Functions ..
83  INTRINSIC max, sqrt
84 * ..
85 * .. Executable Statements ..
86 *
87 * Test the input parameters.
88 *
89  info = 0
90  upper = lsame( uplo, 'U' )
91  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
92  info = -1
93  ELSE IF( n.LT.0 ) THEN
94  info = -2
95  ELSE IF( lda.LT.max( 1, n ) ) THEN
96  info = -4
97  END IF
98  IF( info.NE.0 ) THEN
99  CALL xerbla( 'DPOTF2', -info )
100  RETURN
101  END IF
102 *
103 * Quick return if possible
104 *
105  IF( n.EQ.0 )
106  $ RETURN
107 *
108  IF( upper ) THEN
109 *
110 * Compute the Cholesky factorization A = U'*U.
111 *
112  DO 10 j = 1, n
113 *
114 * Compute U(J,J) and test for non-positive-definiteness.
115 *
116  ajj = a( j, j ) - ddot( j-1, a( 1, j ), 1, a( 1, j ), 1 )
117  IF( ajj.LE.zero ) THEN
118  a( j, j ) = ajj
119  GO TO 30
120  END IF
121  ajj = sqrt( ajj )
122  a( j, j ) = ajj
123 *
124 * Compute elements J+1:N of row J.
125 *
126  IF( j.LT.n ) THEN
127  CALL dgemv( 'Transpose', j-1, n-j, -one, a( 1, j+1 ),
128  $ lda, a( 1, j ), 1, one, a( j, j+1 ), lda )
129  CALL dscal( n-j, one / ajj, a( j, j+1 ), lda )
130  END IF
131  10 CONTINUE
132  ELSE
133 *
134 * Compute the Cholesky factorization A = L*L'.
135 *
136  DO 20 j = 1, n
137 *
138 * Compute L(J,J) and test for non-positive-definiteness.
139 *
140  ajj = a( j, j ) - ddot( j-1, a( j, 1 ), lda, a( j, 1 ),
141  $ lda )
142  IF( ajj.LE.zero ) THEN
143  a( j, j ) = ajj
144  GO TO 30
145  END IF
146  ajj = sqrt( ajj )
147  a( j, j ) = ajj
148 *
149 * Compute elements J+1:N of column J.
150 *
151  IF( j.LT.n ) THEN
152  CALL dgemv( 'No transpose', n-j, j-1, -one, a( j+1, 1 ),
153  $ lda, a( j, 1 ), lda, one, a( j+1, j ), 1 )
154  CALL dscal( n-j, one / ajj, a( j+1, j ), 1 )
155  END IF
156  20 CONTINUE
157  END IF
158  GO TO 40
159 *
160  30 CONTINUE
161  info = j
162 *
163  40 CONTINUE
164  RETURN
165 *
166 * End of DPOTF2
167 *
168  END
subroutine dgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
Definition: dgemv.f:3
subroutine dpotf2(UPLO, N, A, LDA, INFO)
Definition: dpotf2.f:2
subroutine dscal(n, da, dx, incx)
Definition: dscal.f:2
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2