LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ssysv_aa_2stage.f
Go to the documentation of this file.
1*> \brief <b> SSYSV_AA_2STAGE computes the solution to system of linear equations A * X = B for SY matrices</b>
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SSYSV_AA_2STAGE + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssysv_aa_2stage.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssysv_aa_2stage.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssysv_aa_2stage.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SSYSV_AA_2STAGE( UPLO, N, NRHS, A, LDA, TB, LTB,
20* IPIV, IPIV2, B, LDB, WORK, LWORK,
21* INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER N, NRHS, LDA, LTB, LDB, LWORK, INFO
26* ..
27* .. Array Arguments ..
28* INTEGER IPIV( * ), IPIV2( * )
29* REAL A( LDA, * ), TB( * ), B( LDB, *), WORK( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> SSYSV_AA_2STAGE computes the solution to a real system of
39*> linear equations
40*> A * X = B,
41*> where A is an N-by-N symmetric matrix and X and B are N-by-NRHS
42*> matrices.
43*>
44*> Aasen's 2-stage algorithm is used to factor A as
45*> A = U**T * T * U, if UPLO = 'U', or
46*> A = L * T * L**T, if UPLO = 'L',
47*> where U (or L) is a product of permutation and unit upper (lower)
48*> triangular matrices, and T is symmetric and band. The matrix T is
49*> then LU-factored with partial pivoting. The factored form of A
50*> is then used to solve the system of equations A * X = B.
51*>
52*> This is the blocked version of the algorithm, calling Level 3 BLAS.
53*> \endverbatim
54*
55* Arguments:
56* ==========
57*
58*> \param[in] UPLO
59*> \verbatim
60*> UPLO is CHARACTER*1
61*> = 'U': Upper triangle of A is stored;
62*> = 'L': Lower triangle of A is stored.
63*> \endverbatim
64*>
65*> \param[in] N
66*> \verbatim
67*> N is INTEGER
68*> The order of the matrix A. N >= 0.
69*> \endverbatim
70*>
71*> \param[in] NRHS
72*> \verbatim
73*> NRHS is INTEGER
74*> The number of right hand sides, i.e., the number of columns
75*> of the matrix B. NRHS >= 0.
76*> \endverbatim
77*>
78*> \param[in,out] A
79*> \verbatim
80*> A is REAL array, dimension (LDA,N)
81*> On entry, the symmetric matrix A. If UPLO = 'U', the leading
82*> N-by-N upper triangular part of A contains the upper
83*> triangular part of the matrix A, and the strictly lower
84*> triangular part of A is not referenced. If UPLO = 'L', the
85*> leading N-by-N lower triangular part of A contains the lower
86*> triangular part of the matrix A, and the strictly upper
87*> triangular part of A is not referenced.
88*>
89*> On exit, L is stored below (or above) the subdiagonal blocks,
90*> when UPLO is 'L' (or 'U').
91*> \endverbatim
92*>
93*> \param[in] LDA
94*> \verbatim
95*> LDA is INTEGER
96*> The leading dimension of the array A. LDA >= max(1,N).
97*> \endverbatim
98*>
99*> \param[out] TB
100*> \verbatim
101*> TB is REAL array, dimension (MAX(1,LTB))
102*> On exit, details of the LU factorization of the band matrix.
103*> \endverbatim
104*>
105*> \param[in] LTB
106*> \verbatim
107*> LTB is INTEGER
108*> The size of the array TB. LTB >= MAX(1,4*N), internally
109*> used to select NB such that LTB >= (3*NB+1)*N.
110*>
111*> If LTB = -1, then a workspace query is assumed; the
112*> routine only calculates the optimal size of LTB,
113*> returns this value as the first entry of TB, and
114*> no error message related to LTB is issued by XERBLA.
115*> \endverbatim
116*>
117*> \param[out] IPIV
118*> \verbatim
119*> IPIV is INTEGER array, dimension (N)
120*> On exit, it contains the details of the interchanges, i.e.,
121*> the row and column k of A were interchanged with the
122*> row and column IPIV(k).
123*> \endverbatim
124*>
125*> \param[out] IPIV2
126*> \verbatim
127*> IPIV2 is INTEGER array, dimension (N)
128*> On exit, it contains the details of the interchanges, i.e.,
129*> the row and column k of T were interchanged with the
130*> row and column IPIV(k).
131*> \endverbatim
132*>
133*> \param[in,out] B
134*> \verbatim
135*> B is REAL array, dimension (LDB,NRHS)
136*> On entry, the right hand side matrix B.
137*> On exit, the solution matrix X.
138*> \endverbatim
139*>
140*> \param[in] LDB
141*> \verbatim
142*> LDB is INTEGER
143*> The leading dimension of the array B. LDB >= max(1,N).
144*> \endverbatim
145*>
146*> \param[out] WORK
147*> \verbatim
148*> WORK is REAL workspace of size (MAX(1,LWORK))
149*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
150*> \endverbatim
151*>
152*> \param[in] LWORK
153*> \verbatim
154*> LWORK is INTEGER
155*> The size of WORK. LWORK >= MAX(1,N), internally used to
156*> select NB such that LWORK >= N*NB.
157*>
158*> If LWORK = -1, then a workspace query is assumed; the
159*> routine only calculates the optimal size of the WORK array,
160*> returns this value as the first entry of the WORK array, and
161*> no error message related to LWORK is issued by XERBLA.
162*> \endverbatim
163*>
164*> \param[out] INFO
165*> \verbatim
166*> INFO is INTEGER
167*> = 0: successful exit
168*> < 0: if INFO = -i, the i-th argument had an illegal value.
169*> > 0: if INFO = i, band LU factorization failed on i-th column
170*> \endverbatim
171*
172* Authors:
173* ========
174*
175*> \author Univ. of Tennessee
176*> \author Univ. of California Berkeley
177*> \author Univ. of Colorado Denver
178*> \author NAG Ltd.
179*
180*> \ingroup hesv_aa_2stage
181*
182* =====================================================================
183 SUBROUTINE ssysv_aa_2stage( UPLO, N, NRHS, A, LDA, TB, LTB,
184 $ IPIV, IPIV2, B, LDB, WORK, LWORK,
185 $ INFO )
186*
187* -- LAPACK driver routine --
188* -- LAPACK is a software package provided by Univ. of Tennessee, --
189* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
190*
191 IMPLICIT NONE
192*
193* .. Scalar Arguments ..
194 CHARACTER UPLO
195 INTEGER N, NRHS, LDA, LDB, LTB, LWORK, INFO
196* ..
197* .. Array Arguments ..
198 INTEGER IPIV( * ), IPIV2( * )
199 REAL A( LDA, * ), B( LDB, * ), TB( * ), WORK( * )
200* ..
201*
202* =====================================================================
203* ..
204* .. Local Scalars ..
205 LOGICAL UPPER, TQUERY, WQUERY
206 INTEGER LWKMIN, LWKOPT
207* ..
208* .. External Functions ..
209 LOGICAL LSAME
210 EXTERNAL LSAME
211 REAL SROUNDUP_LWORK
212 EXTERNAL sroundup_lwork
213* ..
214* .. External Subroutines ..
216 $ xerbla
217* ..
218* .. Intrinsic Functions ..
219 INTRINSIC max
220* ..
221* .. Executable Statements ..
222*
223* Test the input parameters.
224*
225 info = 0
226 upper = lsame( uplo, 'U' )
227 wquery = ( lwork.EQ.-1 )
228 tquery = ( ltb.EQ.-1 )
229 lwkmin = max( 1, n )
230 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
231 info = -1
232 ELSE IF( n.LT.0 ) THEN
233 info = -2
234 ELSE IF( nrhs.LT.0 ) THEN
235 info = -3
236 ELSE IF( lda.LT.max( 1, n ) ) THEN
237 info = -5
238 ELSE IF( ltb.LT.max( 1, 4*n ) .AND. .NOT.tquery ) THEN
239 info = -7
240 ELSE IF( ldb.LT.max( 1, n ) ) THEN
241 info = -11
242 ELSE IF( lwork.LT.lwkmin .AND. .NOT.wquery ) THEN
243 info = -13
244 END IF
245*
246 IF( info.EQ.0 ) THEN
247 CALL ssytrf_aa_2stage( uplo, n, a, lda, tb, -1, ipiv,
248 $ ipiv2, work, -1, info )
249 lwkopt = max( lwkmin, int( work( 1 ) ) )
250 work( 1 ) = sroundup_lwork( lwkopt )
251 END IF
252*
253 IF( info.NE.0 ) THEN
254 CALL xerbla( 'SSYSV_AA_2STAGE', -info )
255 RETURN
256 ELSE IF( wquery .OR. tquery ) THEN
257 RETURN
258 END IF
259*
260* Compute the factorization A = U**T*T*U or A = L*T*L**T.
261*
262 CALL ssytrf_aa_2stage( uplo, n, a, lda, tb, ltb, ipiv, ipiv2,
263 $ work, lwork, info )
264 IF( info.EQ.0 ) THEN
265*
266* Solve the system A*X = B, overwriting B with X.
267*
268 CALL ssytrs_aa_2stage( uplo, n, nrhs, a, lda, tb, ltb, ipiv,
269 $ ipiv2, b, ldb, info )
270*
271 END IF
272*
273 work( 1 ) = sroundup_lwork( lwkopt )
274*
275 RETURN
276*
277* End of SSYSV_AA_2STAGE
278*
279 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssysv_aa_2stage(uplo, n, nrhs, a, lda, tb, ltb, ipiv, ipiv2, b, ldb, work, lwork, info)
SSYSV_AA_2STAGE computes the solution to system of linear equations A * X = B for SY matrices
subroutine ssytrf_aa_2stage(uplo, n, a, lda, tb, ltb, ipiv, ipiv2, work, lwork, info)
SSYTRF_AA_2STAGE
subroutine ssytrs_aa_2stage(uplo, n, nrhs, a, lda, tb, ltb, ipiv, ipiv2, b, ldb, info)
SSYTRS_AA_2STAGE