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