LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cptsv.f
Go to the documentation of this file.
1*> \brief <b> CPTSV computes the solution to system of linear equations A * X = B for PT matrices</b>
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CPTSV + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cptsv.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cptsv.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cptsv.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE CPTSV( N, NRHS, D, E, B, LDB, INFO )
22*
23* .. Scalar Arguments ..
24* INTEGER INFO, LDB, N, NRHS
25* ..
26* .. Array Arguments ..
27* REAL D( * )
28* COMPLEX B( LDB, * ), E( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> CPTSV computes the solution to a complex system of linear equations
38*> A*X = B, where A is an N-by-N Hermitian positive definite tridiagonal
39*> matrix, and X and B are N-by-NRHS matrices.
40*>
41*> A is factored as A = L*D*L**H, and the factored form of A is then
42*> used to solve the system of equations.
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The order of the matrix A. N >= 0.
52*> \endverbatim
53*>
54*> \param[in] NRHS
55*> \verbatim
56*> NRHS is INTEGER
57*> The number of right hand sides, i.e., the number of columns
58*> of the matrix B. NRHS >= 0.
59*> \endverbatim
60*>
61*> \param[in,out] D
62*> \verbatim
63*> D is REAL array, dimension (N)
64*> On entry, the n diagonal elements of the tridiagonal matrix
65*> A. On exit, the n diagonal elements of the diagonal matrix
66*> D from the factorization A = L*D*L**H.
67*> \endverbatim
68*>
69*> \param[in,out] E
70*> \verbatim
71*> E is COMPLEX array, dimension (N-1)
72*> On entry, the (n-1) subdiagonal elements of the tridiagonal
73*> matrix A. On exit, the (n-1) subdiagonal elements of the
74*> unit bidiagonal factor L from the L*D*L**H factorization of
75*> A. E can also be regarded as the superdiagonal of the unit
76*> bidiagonal factor U from the U**H*D*U factorization of A.
77*> \endverbatim
78*>
79*> \param[in,out] B
80*> \verbatim
81*> B is COMPLEX array, dimension (LDB,NRHS)
82*> On entry, the N-by-NRHS right hand side matrix B.
83*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
84*> \endverbatim
85*>
86*> \param[in] LDB
87*> \verbatim
88*> LDB is INTEGER
89*> The leading dimension of the array B. LDB >= max(1,N).
90*> \endverbatim
91*>
92*> \param[out] INFO
93*> \verbatim
94*> INFO is INTEGER
95*> = 0: successful exit
96*> < 0: if INFO = -i, the i-th argument had an illegal value
97*> > 0: if INFO = i, the leading principal minor of order i
98*> is not positive, and the solution has not been
99*> computed. The factorization has not been completed
100*> unless i = N.
101*> \endverbatim
102*
103* Authors:
104* ========
105*
106*> \author Univ. of Tennessee
107*> \author Univ. of California Berkeley
108*> \author Univ. of Colorado Denver
109*> \author NAG Ltd.
110*
111*> \ingroup ptsv
112*
113* =====================================================================
114 SUBROUTINE cptsv( N, NRHS, D, E, B, LDB, INFO )
115*
116* -- LAPACK driver routine --
117* -- LAPACK is a software package provided by Univ. of Tennessee, --
118* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
119*
120* .. Scalar Arguments ..
121 INTEGER INFO, LDB, N, NRHS
122* ..
123* .. Array Arguments ..
124 REAL D( * )
125 COMPLEX B( LDB, * ), E( * )
126* ..
127*
128* =====================================================================
129*
130* .. External Subroutines ..
131 EXTERNAL cpttrf, cpttrs, xerbla
132* ..
133* .. Intrinsic Functions ..
134 INTRINSIC max
135* ..
136* .. Executable Statements ..
137*
138* Test the input parameters.
139*
140 info = 0
141 IF( n.LT.0 ) THEN
142 info = -1
143 ELSE IF( nrhs.LT.0 ) THEN
144 info = -2
145 ELSE IF( ldb.LT.max( 1, n ) ) THEN
146 info = -6
147 END IF
148 IF( info.NE.0 ) THEN
149 CALL xerbla( 'CPTSV ', -info )
150 RETURN
151 END IF
152*
153* Compute the L*D*L**H (or U**H*D*U) factorization of A.
154*
155 CALL cpttrf( n, d, e, info )
156 IF( info.EQ.0 ) THEN
157*
158* Solve the system A*X = B, overwriting B with X.
159*
160 CALL cpttrs( 'Lower', n, nrhs, d, e, b, ldb, info )
161 END IF
162 RETURN
163*
164* End of CPTSV
165*
166 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cptsv(n, nrhs, d, e, b, ldb, info)
CPTSV computes the solution to system of linear equations A * X = B for PT matrices
Definition cptsv.f:115
subroutine cpttrf(n, d, e, info)
CPTTRF
Definition cpttrf.f:92
subroutine cpttrs(uplo, n, nrhs, d, e, b, ldb, info)
CPTTRS
Definition cpttrs.f:121