LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cpptrs.f
Go to the documentation of this file.
1*> \brief \b CPPTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CPPTRS + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpptrs.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpptrs.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpptrs.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE CPPTRS( UPLO, N, NRHS, AP, B, LDB, INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER INFO, LDB, N, NRHS
26* ..
27* .. Array Arguments ..
28* COMPLEX AP( * ), B( LDB, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> CPPTRS solves a system of linear equations A*X = B with a Hermitian
38*> positive definite matrix A in packed storage using the Cholesky
39*> factorization A = U**H*U or A = L*L**H computed by CPPTRF.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] UPLO
46*> \verbatim
47*> UPLO is CHARACTER*1
48*> = 'U': Upper triangle of A is stored;
49*> = 'L': Lower triangle of A is stored.
50*> \endverbatim
51*>
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The order of the matrix A. N >= 0.
56*> \endverbatim
57*>
58*> \param[in] NRHS
59*> \verbatim
60*> NRHS is INTEGER
61*> The number of right hand sides, i.e., the number of columns
62*> of the matrix B. NRHS >= 0.
63*> \endverbatim
64*>
65*> \param[in] AP
66*> \verbatim
67*> AP is COMPLEX array, dimension (N*(N+1)/2)
68*> The triangular factor U or L from the Cholesky factorization
69*> A = U**H*U or A = L*L**H, packed columnwise in a linear
70*> array. The j-th column of U or L is stored in the array AP
71*> as follows:
72*> if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
73*> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=n.
74*> \endverbatim
75*>
76*> \param[in,out] B
77*> \verbatim
78*> B is COMPLEX array, dimension (LDB,NRHS)
79*> On entry, the right hand side matrix B.
80*> On exit, the solution matrix X.
81*> \endverbatim
82*>
83*> \param[in] LDB
84*> \verbatim
85*> LDB is INTEGER
86*> The leading dimension of the array B. LDB >= max(1,N).
87*> \endverbatim
88*>
89*> \param[out] INFO
90*> \verbatim
91*> INFO is INTEGER
92*> = 0: successful exit
93*> < 0: if INFO = -i, the i-th argument had an illegal value
94*> \endverbatim
95*
96* Authors:
97* ========
98*
99*> \author Univ. of Tennessee
100*> \author Univ. of California Berkeley
101*> \author Univ. of Colorado Denver
102*> \author NAG Ltd.
103*
104*> \ingroup pptrs
105*
106* =====================================================================
107 SUBROUTINE cpptrs( UPLO, N, NRHS, AP, B, LDB, INFO )
108*
109* -- LAPACK computational routine --
110* -- LAPACK is a software package provided by Univ. of Tennessee, --
111* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
112*
113* .. Scalar Arguments ..
114 CHARACTER UPLO
115 INTEGER INFO, LDB, N, NRHS
116* ..
117* .. Array Arguments ..
118 COMPLEX AP( * ), B( LDB, * )
119* ..
120*
121* =====================================================================
122*
123* .. Local Scalars ..
124 LOGICAL UPPER
125 INTEGER I
126* ..
127* .. External Functions ..
128 LOGICAL LSAME
129 EXTERNAL lsame
130* ..
131* .. External Subroutines ..
132 EXTERNAL ctpsv, xerbla
133* ..
134* .. Intrinsic Functions ..
135 INTRINSIC max
136* ..
137* .. Executable Statements ..
138*
139* Test the input parameters.
140*
141 info = 0
142 upper = lsame( uplo, 'U' )
143 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
144 info = -1
145 ELSE IF( n.LT.0 ) THEN
146 info = -2
147 ELSE IF( nrhs.LT.0 ) THEN
148 info = -3
149 ELSE IF( ldb.LT.max( 1, n ) ) THEN
150 info = -6
151 END IF
152 IF( info.NE.0 ) THEN
153 CALL xerbla( 'CPPTRS', -info )
154 RETURN
155 END IF
156*
157* Quick return if possible
158*
159 IF( n.EQ.0 .OR. nrhs.EQ.0 )
160 $ RETURN
161*
162 IF( upper ) THEN
163*
164* Solve A*X = B where A = U**H * U.
165*
166 DO 10 i = 1, nrhs
167*
168* Solve U**H *X = B, overwriting B with X.
169*
170 CALL ctpsv( 'Upper', 'Conjugate transpose', 'Non-unit', n,
171 $ ap, b( 1, i ), 1 )
172*
173* Solve U*X = B, overwriting B with X.
174*
175 CALL ctpsv( 'Upper', 'No transpose', 'Non-unit', n, ap,
176 $ b( 1, i ), 1 )
177 10 CONTINUE
178 ELSE
179*
180* Solve A*X = B where A = L * L**H.
181*
182 DO 20 i = 1, nrhs
183*
184* Solve L*Y = B, overwriting B with X.
185*
186 CALL ctpsv( 'Lower', 'No transpose', 'Non-unit', n, ap,
187 $ b( 1, i ), 1 )
188*
189* Solve L**H *X = Y, overwriting B with X.
190*
191 CALL ctpsv( 'Lower', 'Conjugate transpose', 'Non-unit', n,
192 $ ap, b( 1, i ), 1 )
193 20 CONTINUE
194 END IF
195*
196 RETURN
197*
198* End of CPPTRS
199*
200 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cpptrs(uplo, n, nrhs, ap, b, ldb, info)
CPPTRS
Definition cpptrs.f:108
subroutine ctpsv(uplo, trans, diag, n, ap, x, incx)
CTPSV
Definition ctpsv.f:144