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