1 SUBROUTINE ZPBTF2( UPLO, N, KD, AB, LDAB, INFO )
2 *
3 * -- LAPACK routine (version 3.3.1) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * -- April 2011 --
7 *
8 * .. Scalar Arguments ..
9 CHARACTER UPLO
10 INTEGER INFO, KD, LDAB, N
11 * ..
12 * .. Array Arguments ..
13 COMPLEX*16 AB( LDAB, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * ZPBTF2 computes the Cholesky factorization of a complex Hermitian
20 * positive definite band matrix A.
21 *
22 * The factorization has the form
23 * A = U**H * U , if UPLO = 'U', or
24 * A = L * L**H, if UPLO = 'L',
25 * where U is an upper triangular matrix, U**H is the conjugate transpose
26 * of U, and L is lower triangular.
27 *
28 * This is the unblocked version of the algorithm, calling Level 2 BLAS.
29 *
30 * Arguments
31 * =========
32 *
33 * UPLO (input) CHARACTER*1
34 * Specifies whether the upper or lower triangular part of the
35 * Hermitian matrix A is stored:
36 * = 'U': Upper triangular
37 * = 'L': Lower triangular
38 *
39 * N (input) INTEGER
40 * The order of the matrix A. N >= 0.
41 *
42 * KD (input) INTEGER
43 * The number of super-diagonals of the matrix A if UPLO = 'U',
44 * or the number of sub-diagonals if UPLO = 'L'. KD >= 0.
45 *
46 * AB (input/output) COMPLEX*16 array, dimension (LDAB,N)
47 * On entry, the upper or lower triangle of the Hermitian band
48 * matrix A, stored in the first KD+1 rows of the array. The
49 * j-th column of A is stored in the j-th column of the array AB
50 * as follows:
51 * if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
52 * if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
53 *
54 * On exit, if INFO = 0, the triangular factor U or L from the
55 * Cholesky factorization A = U**H *U or A = L*L**H of the band
56 * matrix A, in the same storage format as A.
57 *
58 * LDAB (input) INTEGER
59 * The leading dimension of the array AB. LDAB >= KD+1.
60 *
61 * INFO (output) INTEGER
62 * = 0: successful exit
63 * < 0: if INFO = -k, the k-th argument had an illegal value
64 * > 0: if INFO = k, the leading minor of order k is not
65 * positive definite, and the factorization could not be
66 * completed.
67 *
68 * Further Details
69 * ===============
70 *
71 * The band storage scheme is illustrated by the following example, when
72 * N = 6, KD = 2, and UPLO = 'U':
73 *
74 * On entry: On exit:
75 *
76 * * * a13 a24 a35 a46 * * u13 u24 u35 u46
77 * * a12 a23 a34 a45 a56 * u12 u23 u34 u45 u56
78 * a11 a22 a33 a44 a55 a66 u11 u22 u33 u44 u55 u66
79 *
80 * Similarly, if UPLO = 'L' the format of A is as follows:
81 *
82 * On entry: On exit:
83 *
84 * a11 a22 a33 a44 a55 a66 l11 l22 l33 l44 l55 l66
85 * a21 a32 a43 a54 a65 * l21 l32 l43 l54 l65 *
86 * a31 a42 a53 a64 * * l31 l42 l53 l64 * *
87 *
88 * Array elements marked * are not used by the routine.
89 *
90 * =====================================================================
91 *
92 * .. Parameters ..
93 DOUBLE PRECISION ONE, ZERO
94 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
95 * ..
96 * .. Local Scalars ..
97 LOGICAL UPPER
98 INTEGER J, KLD, KN
99 DOUBLE PRECISION AJJ
100 * ..
101 * .. External Functions ..
102 LOGICAL LSAME
103 EXTERNAL LSAME
104 * ..
105 * .. External Subroutines ..
106 EXTERNAL XERBLA, ZDSCAL, ZHER, ZLACGV
107 * ..
108 * .. Intrinsic Functions ..
109 INTRINSIC DBLE, MAX, MIN, SQRT
110 * ..
111 * .. Executable Statements ..
112 *
113 * Test the input parameters.
114 *
115 INFO = 0
116 UPPER = LSAME( UPLO, 'U' )
117 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
118 INFO = -1
119 ELSE IF( N.LT.0 ) THEN
120 INFO = -2
121 ELSE IF( KD.LT.0 ) THEN
122 INFO = -3
123 ELSE IF( LDAB.LT.KD+1 ) THEN
124 INFO = -5
125 END IF
126 IF( INFO.NE.0 ) THEN
127 CALL XERBLA( 'ZPBTF2', -INFO )
128 RETURN
129 END IF
130 *
131 * Quick return if possible
132 *
133 IF( N.EQ.0 )
134 $ RETURN
135 *
136 KLD = MAX( 1, LDAB-1 )
137 *
138 IF( UPPER ) THEN
139 *
140 * Compute the Cholesky factorization A = U**H * U.
141 *
142 DO 10 J = 1, N
143 *
144 * Compute U(J,J) and test for non-positive-definiteness.
145 *
146 AJJ = DBLE( AB( KD+1, J ) )
147 IF( AJJ.LE.ZERO ) THEN
148 AB( KD+1, J ) = AJJ
149 GO TO 30
150 END IF
151 AJJ = SQRT( AJJ )
152 AB( KD+1, J ) = AJJ
153 *
154 * Compute elements J+1:J+KN of row J and update the
155 * trailing submatrix within the band.
156 *
157 KN = MIN( KD, N-J )
158 IF( KN.GT.0 ) THEN
159 CALL ZDSCAL( KN, ONE / AJJ, AB( KD, J+1 ), KLD )
160 CALL ZLACGV( KN, AB( KD, J+1 ), KLD )
161 CALL ZHER( 'Upper', KN, -ONE, AB( KD, J+1 ), KLD,
162 $ AB( KD+1, J+1 ), KLD )
163 CALL ZLACGV( KN, AB( KD, J+1 ), KLD )
164 END IF
165 10 CONTINUE
166 ELSE
167 *
168 * Compute the Cholesky factorization A = L*L**H.
169 *
170 DO 20 J = 1, N
171 *
172 * Compute L(J,J) and test for non-positive-definiteness.
173 *
174 AJJ = DBLE( AB( 1, J ) )
175 IF( AJJ.LE.ZERO ) THEN
176 AB( 1, J ) = AJJ
177 GO TO 30
178 END IF
179 AJJ = SQRT( AJJ )
180 AB( 1, J ) = AJJ
181 *
182 * Compute elements J+1:J+KN of column J and update the
183 * trailing submatrix within the band.
184 *
185 KN = MIN( KD, N-J )
186 IF( KN.GT.0 ) THEN
187 CALL ZDSCAL( KN, ONE / AJJ, AB( 2, J ), 1 )
188 CALL ZHER( 'Lower', KN, -ONE, AB( 2, J ), 1,
189 $ AB( 1, J+1 ), KLD )
190 END IF
191 20 CONTINUE
192 END IF
193 RETURN
194 *
195 30 CONTINUE
196 INFO = J
197 RETURN
198 *
199 * End of ZPBTF2
200 *
201 END
2 *
3 * -- LAPACK routine (version 3.3.1) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * -- April 2011 --
7 *
8 * .. Scalar Arguments ..
9 CHARACTER UPLO
10 INTEGER INFO, KD, LDAB, N
11 * ..
12 * .. Array Arguments ..
13 COMPLEX*16 AB( LDAB, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * ZPBTF2 computes the Cholesky factorization of a complex Hermitian
20 * positive definite band matrix A.
21 *
22 * The factorization has the form
23 * A = U**H * U , if UPLO = 'U', or
24 * A = L * L**H, if UPLO = 'L',
25 * where U is an upper triangular matrix, U**H is the conjugate transpose
26 * of U, and L is lower triangular.
27 *
28 * This is the unblocked version of the algorithm, calling Level 2 BLAS.
29 *
30 * Arguments
31 * =========
32 *
33 * UPLO (input) CHARACTER*1
34 * Specifies whether the upper or lower triangular part of the
35 * Hermitian matrix A is stored:
36 * = 'U': Upper triangular
37 * = 'L': Lower triangular
38 *
39 * N (input) INTEGER
40 * The order of the matrix A. N >= 0.
41 *
42 * KD (input) INTEGER
43 * The number of super-diagonals of the matrix A if UPLO = 'U',
44 * or the number of sub-diagonals if UPLO = 'L'. KD >= 0.
45 *
46 * AB (input/output) COMPLEX*16 array, dimension (LDAB,N)
47 * On entry, the upper or lower triangle of the Hermitian band
48 * matrix A, stored in the first KD+1 rows of the array. The
49 * j-th column of A is stored in the j-th column of the array AB
50 * as follows:
51 * if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
52 * if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
53 *
54 * On exit, if INFO = 0, the triangular factor U or L from the
55 * Cholesky factorization A = U**H *U or A = L*L**H of the band
56 * matrix A, in the same storage format as A.
57 *
58 * LDAB (input) INTEGER
59 * The leading dimension of the array AB. LDAB >= KD+1.
60 *
61 * INFO (output) INTEGER
62 * = 0: successful exit
63 * < 0: if INFO = -k, the k-th argument had an illegal value
64 * > 0: if INFO = k, the leading minor of order k is not
65 * positive definite, and the factorization could not be
66 * completed.
67 *
68 * Further Details
69 * ===============
70 *
71 * The band storage scheme is illustrated by the following example, when
72 * N = 6, KD = 2, and UPLO = 'U':
73 *
74 * On entry: On exit:
75 *
76 * * * a13 a24 a35 a46 * * u13 u24 u35 u46
77 * * a12 a23 a34 a45 a56 * u12 u23 u34 u45 u56
78 * a11 a22 a33 a44 a55 a66 u11 u22 u33 u44 u55 u66
79 *
80 * Similarly, if UPLO = 'L' the format of A is as follows:
81 *
82 * On entry: On exit:
83 *
84 * a11 a22 a33 a44 a55 a66 l11 l22 l33 l44 l55 l66
85 * a21 a32 a43 a54 a65 * l21 l32 l43 l54 l65 *
86 * a31 a42 a53 a64 * * l31 l42 l53 l64 * *
87 *
88 * Array elements marked * are not used by the routine.
89 *
90 * =====================================================================
91 *
92 * .. Parameters ..
93 DOUBLE PRECISION ONE, ZERO
94 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
95 * ..
96 * .. Local Scalars ..
97 LOGICAL UPPER
98 INTEGER J, KLD, KN
99 DOUBLE PRECISION AJJ
100 * ..
101 * .. External Functions ..
102 LOGICAL LSAME
103 EXTERNAL LSAME
104 * ..
105 * .. External Subroutines ..
106 EXTERNAL XERBLA, ZDSCAL, ZHER, ZLACGV
107 * ..
108 * .. Intrinsic Functions ..
109 INTRINSIC DBLE, MAX, MIN, SQRT
110 * ..
111 * .. Executable Statements ..
112 *
113 * Test the input parameters.
114 *
115 INFO = 0
116 UPPER = LSAME( UPLO, 'U' )
117 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
118 INFO = -1
119 ELSE IF( N.LT.0 ) THEN
120 INFO = -2
121 ELSE IF( KD.LT.0 ) THEN
122 INFO = -3
123 ELSE IF( LDAB.LT.KD+1 ) THEN
124 INFO = -5
125 END IF
126 IF( INFO.NE.0 ) THEN
127 CALL XERBLA( 'ZPBTF2', -INFO )
128 RETURN
129 END IF
130 *
131 * Quick return if possible
132 *
133 IF( N.EQ.0 )
134 $ RETURN
135 *
136 KLD = MAX( 1, LDAB-1 )
137 *
138 IF( UPPER ) THEN
139 *
140 * Compute the Cholesky factorization A = U**H * U.
141 *
142 DO 10 J = 1, N
143 *
144 * Compute U(J,J) and test for non-positive-definiteness.
145 *
146 AJJ = DBLE( AB( KD+1, J ) )
147 IF( AJJ.LE.ZERO ) THEN
148 AB( KD+1, J ) = AJJ
149 GO TO 30
150 END IF
151 AJJ = SQRT( AJJ )
152 AB( KD+1, J ) = AJJ
153 *
154 * Compute elements J+1:J+KN of row J and update the
155 * trailing submatrix within the band.
156 *
157 KN = MIN( KD, N-J )
158 IF( KN.GT.0 ) THEN
159 CALL ZDSCAL( KN, ONE / AJJ, AB( KD, J+1 ), KLD )
160 CALL ZLACGV( KN, AB( KD, J+1 ), KLD )
161 CALL ZHER( 'Upper', KN, -ONE, AB( KD, J+1 ), KLD,
162 $ AB( KD+1, J+1 ), KLD )
163 CALL ZLACGV( KN, AB( KD, J+1 ), KLD )
164 END IF
165 10 CONTINUE
166 ELSE
167 *
168 * Compute the Cholesky factorization A = L*L**H.
169 *
170 DO 20 J = 1, N
171 *
172 * Compute L(J,J) and test for non-positive-definiteness.
173 *
174 AJJ = DBLE( AB( 1, J ) )
175 IF( AJJ.LE.ZERO ) THEN
176 AB( 1, J ) = AJJ
177 GO TO 30
178 END IF
179 AJJ = SQRT( AJJ )
180 AB( 1, J ) = AJJ
181 *
182 * Compute elements J+1:J+KN of column J and update the
183 * trailing submatrix within the band.
184 *
185 KN = MIN( KD, N-J )
186 IF( KN.GT.0 ) THEN
187 CALL ZDSCAL( KN, ONE / AJJ, AB( 2, J ), 1 )
188 CALL ZHER( 'Lower', KN, -ONE, AB( 2, J ), 1,
189 $ AB( 1, J+1 ), KLD )
190 END IF
191 20 CONTINUE
192 END IF
193 RETURN
194 *
195 30 CONTINUE
196 INFO = J
197 RETURN
198 *
199 * End of ZPBTF2
200 *
201 END