1 SUBROUTINE ZPBSV( UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO )
2 *
3 * -- LAPACK driver 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, LDB, N, NRHS
11 * ..
12 * .. Array Arguments ..
13 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * ZPBSV computes the solution to a complex system of linear equations
20 * A * X = B,
21 * where A is an N-by-N Hermitian positive definite band matrix and X
22 * and B are N-by-NRHS matrices.
23 *
24 * The Cholesky decomposition is used to factor A as
25 * A = U**H * U, if UPLO = 'U', or
26 * A = L * L**H, if UPLO = 'L',
27 * where U is an upper triangular band matrix, and L is a lower
28 * triangular band matrix, with the same number of superdiagonals or
29 * subdiagonals as A. The factored form of A is then used to solve the
30 * system of equations A * X = B.
31 *
32 * Arguments
33 * =========
34 *
35 * UPLO (input) CHARACTER*1
36 * = 'U': Upper triangle of A is stored;
37 * = 'L': Lower triangle of A is stored.
38 *
39 * N (input) INTEGER
40 * The number of linear equations, i.e., the order of the
41 * matrix A. N >= 0.
42 *
43 * KD (input) INTEGER
44 * The number of superdiagonals of the matrix A if UPLO = 'U',
45 * or the number of subdiagonals if UPLO = 'L'. KD >= 0.
46 *
47 * NRHS (input) INTEGER
48 * The number of right hand sides, i.e., the number of columns
49 * of the matrix B. NRHS >= 0.
50 *
51 * AB (input/output) COMPLEX*16 array, dimension (LDAB,N)
52 * On entry, the upper or lower triangle of the Hermitian band
53 * matrix A, stored in the first KD+1 rows of the array. The
54 * j-th column of A is stored in the j-th column of the array AB
55 * as follows:
56 * if UPLO = 'U', AB(KD+1+i-j,j) = A(i,j) for max(1,j-KD)<=i<=j;
57 * if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(N,j+KD).
58 * See below for further details.
59 *
60 * On exit, if INFO = 0, the triangular factor U or L from the
61 * Cholesky factorization A = U**H *U or A = L*L**H of the band
62 * matrix A, in the same storage format as A.
63 *
64 * LDAB (input) INTEGER
65 * The leading dimension of the array AB. LDAB >= KD+1.
66 *
67 * B (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
68 * On entry, the N-by-NRHS right hand side matrix B.
69 * On exit, if INFO = 0, the N-by-NRHS solution matrix X.
70 *
71 * LDB (input) INTEGER
72 * The leading dimension of the array B. LDB >= max(1,N).
73 *
74 * INFO (output) INTEGER
75 * = 0: successful exit
76 * < 0: if INFO = -i, the i-th argument had an illegal value
77 * > 0: if INFO = i, the leading minor of order i of A is not
78 * positive definite, so the factorization could not be
79 * completed, and the solution has not been computed.
80 *
81 * Further Details
82 * ===============
83 *
84 * The band storage scheme is illustrated by the following example, when
85 * N = 6, KD = 2, and UPLO = 'U':
86 *
87 * On entry: On exit:
88 *
89 * * * a13 a24 a35 a46 * * u13 u24 u35 u46
90 * * a12 a23 a34 a45 a56 * u12 u23 u34 u45 u56
91 * a11 a22 a33 a44 a55 a66 u11 u22 u33 u44 u55 u66
92 *
93 * Similarly, if UPLO = 'L' the format of A is as follows:
94 *
95 * On entry: On exit:
96 *
97 * a11 a22 a33 a44 a55 a66 l11 l22 l33 l44 l55 l66
98 * a21 a32 a43 a54 a65 * l21 l32 l43 l54 l65 *
99 * a31 a42 a53 a64 * * l31 l42 l53 l64 * *
100 *
101 * Array elements marked * are not used by the routine.
102 *
103 * =====================================================================
104 *
105 * .. External Functions ..
106 LOGICAL LSAME
107 EXTERNAL LSAME
108 * ..
109 * .. External Subroutines ..
110 EXTERNAL XERBLA, ZPBTRF, ZPBTRS
111 * ..
112 * .. Intrinsic Functions ..
113 INTRINSIC MAX
114 * ..
115 * .. Executable Statements ..
116 *
117 * Test the input parameters.
118 *
119 INFO = 0
120 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
121 INFO = -1
122 ELSE IF( N.LT.0 ) THEN
123 INFO = -2
124 ELSE IF( KD.LT.0 ) THEN
125 INFO = -3
126 ELSE IF( NRHS.LT.0 ) THEN
127 INFO = -4
128 ELSE IF( LDAB.LT.KD+1 ) THEN
129 INFO = -6
130 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
131 INFO = -8
132 END IF
133 IF( INFO.NE.0 ) THEN
134 CALL XERBLA( 'ZPBSV ', -INFO )
135 RETURN
136 END IF
137 *
138 * Compute the Cholesky factorization A = U**H *U or A = L*L**H.
139 *
140 CALL ZPBTRF( UPLO, N, KD, AB, LDAB, INFO )
141 IF( INFO.EQ.0 ) THEN
142 *
143 * Solve the system A*X = B, overwriting B with X.
144 *
145 CALL ZPBTRS( UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO )
146 *
147 END IF
148 RETURN
149 *
150 * End of ZPBSV
151 *
152 END
2 *
3 * -- LAPACK driver 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, LDB, N, NRHS
11 * ..
12 * .. Array Arguments ..
13 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * ZPBSV computes the solution to a complex system of linear equations
20 * A * X = B,
21 * where A is an N-by-N Hermitian positive definite band matrix and X
22 * and B are N-by-NRHS matrices.
23 *
24 * The Cholesky decomposition is used to factor A as
25 * A = U**H * U, if UPLO = 'U', or
26 * A = L * L**H, if UPLO = 'L',
27 * where U is an upper triangular band matrix, and L is a lower
28 * triangular band matrix, with the same number of superdiagonals or
29 * subdiagonals as A. The factored form of A is then used to solve the
30 * system of equations A * X = B.
31 *
32 * Arguments
33 * =========
34 *
35 * UPLO (input) CHARACTER*1
36 * = 'U': Upper triangle of A is stored;
37 * = 'L': Lower triangle of A is stored.
38 *
39 * N (input) INTEGER
40 * The number of linear equations, i.e., the order of the
41 * matrix A. N >= 0.
42 *
43 * KD (input) INTEGER
44 * The number of superdiagonals of the matrix A if UPLO = 'U',
45 * or the number of subdiagonals if UPLO = 'L'. KD >= 0.
46 *
47 * NRHS (input) INTEGER
48 * The number of right hand sides, i.e., the number of columns
49 * of the matrix B. NRHS >= 0.
50 *
51 * AB (input/output) COMPLEX*16 array, dimension (LDAB,N)
52 * On entry, the upper or lower triangle of the Hermitian band
53 * matrix A, stored in the first KD+1 rows of the array. The
54 * j-th column of A is stored in the j-th column of the array AB
55 * as follows:
56 * if UPLO = 'U', AB(KD+1+i-j,j) = A(i,j) for max(1,j-KD)<=i<=j;
57 * if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(N,j+KD).
58 * See below for further details.
59 *
60 * On exit, if INFO = 0, the triangular factor U or L from the
61 * Cholesky factorization A = U**H *U or A = L*L**H of the band
62 * matrix A, in the same storage format as A.
63 *
64 * LDAB (input) INTEGER
65 * The leading dimension of the array AB. LDAB >= KD+1.
66 *
67 * B (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
68 * On entry, the N-by-NRHS right hand side matrix B.
69 * On exit, if INFO = 0, the N-by-NRHS solution matrix X.
70 *
71 * LDB (input) INTEGER
72 * The leading dimension of the array B. LDB >= max(1,N).
73 *
74 * INFO (output) INTEGER
75 * = 0: successful exit
76 * < 0: if INFO = -i, the i-th argument had an illegal value
77 * > 0: if INFO = i, the leading minor of order i of A is not
78 * positive definite, so the factorization could not be
79 * completed, and the solution has not been computed.
80 *
81 * Further Details
82 * ===============
83 *
84 * The band storage scheme is illustrated by the following example, when
85 * N = 6, KD = 2, and UPLO = 'U':
86 *
87 * On entry: On exit:
88 *
89 * * * a13 a24 a35 a46 * * u13 u24 u35 u46
90 * * a12 a23 a34 a45 a56 * u12 u23 u34 u45 u56
91 * a11 a22 a33 a44 a55 a66 u11 u22 u33 u44 u55 u66
92 *
93 * Similarly, if UPLO = 'L' the format of A is as follows:
94 *
95 * On entry: On exit:
96 *
97 * a11 a22 a33 a44 a55 a66 l11 l22 l33 l44 l55 l66
98 * a21 a32 a43 a54 a65 * l21 l32 l43 l54 l65 *
99 * a31 a42 a53 a64 * * l31 l42 l53 l64 * *
100 *
101 * Array elements marked * are not used by the routine.
102 *
103 * =====================================================================
104 *
105 * .. External Functions ..
106 LOGICAL LSAME
107 EXTERNAL LSAME
108 * ..
109 * .. External Subroutines ..
110 EXTERNAL XERBLA, ZPBTRF, ZPBTRS
111 * ..
112 * .. Intrinsic Functions ..
113 INTRINSIC MAX
114 * ..
115 * .. Executable Statements ..
116 *
117 * Test the input parameters.
118 *
119 INFO = 0
120 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
121 INFO = -1
122 ELSE IF( N.LT.0 ) THEN
123 INFO = -2
124 ELSE IF( KD.LT.0 ) THEN
125 INFO = -3
126 ELSE IF( NRHS.LT.0 ) THEN
127 INFO = -4
128 ELSE IF( LDAB.LT.KD+1 ) THEN
129 INFO = -6
130 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
131 INFO = -8
132 END IF
133 IF( INFO.NE.0 ) THEN
134 CALL XERBLA( 'ZPBSV ', -INFO )
135 RETURN
136 END IF
137 *
138 * Compute the Cholesky factorization A = U**H *U or A = L*L**H.
139 *
140 CALL ZPBTRF( UPLO, N, KD, AB, LDAB, INFO )
141 IF( INFO.EQ.0 ) THEN
142 *
143 * Solve the system A*X = B, overwriting B with X.
144 *
145 CALL ZPBTRS( UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO )
146 *
147 END IF
148 RETURN
149 *
150 * End of ZPBSV
151 *
152 END