LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dsysv_aa.f
Go to the documentation of this file.
1*> \brief <b> DSYSV_AA 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 DSYSV_AA + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsysv_aa.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsysv_aa.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsysv_aa.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DSYSV_AA( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
20* LWORK, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER UPLO
24* INTEGER N, NRHS, LDA, LDB, LWORK, INFO
25* ..
26* .. Array Arguments ..
27* INTEGER IPIV( * )
28* DOUBLE PRECISION A( LDA, * ), B( LDB, * ), WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> DSYSV computes the solution to a real system of linear equations
38*> A * X = B,
39*> where A is an N-by-N symmetric matrix and X and B are N-by-NRHS
40*> matrices.
41*>
42*> Aasen's algorithm is used to factor A as
43*> A = U**T * T * U, if UPLO = 'U', or
44*> A = L * T * L**T, if UPLO = 'L',
45*> where U (or L) is a product of permutation and unit upper (lower)
46*> triangular matrices, and T is symmetric tridiagonal. The factored
47*> form of A is then used to solve the system of equations A * X = B.
48*> \endverbatim
49*
50* Arguments:
51* ==========
52*
53*> \param[in] UPLO
54*> \verbatim
55*> UPLO is CHARACTER*1
56*> = 'U': Upper triangle of A is stored;
57*> = 'L': Lower triangle of A is stored.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> The number of linear equations, i.e., the order of the
64*> matrix A. N >= 0.
65*> \endverbatim
66*>
67*> \param[in] NRHS
68*> \verbatim
69*> NRHS is INTEGER
70*> The number of right hand sides, i.e., the number of columns
71*> of the matrix B. NRHS >= 0.
72*> \endverbatim
73*>
74*> \param[in,out] A
75*> \verbatim
76*> A is DOUBLE PRECISION array, dimension (LDA,N)
77*> On entry, the symmetric matrix A. If UPLO = 'U', the leading
78*> N-by-N upper triangular part of A contains the upper
79*> triangular part of the matrix A, and the strictly lower
80*> triangular part of A is not referenced. If UPLO = 'L', the
81*> leading N-by-N lower triangular part of A contains the lower
82*> triangular part of the matrix A, and the strictly upper
83*> triangular part of A is not referenced.
84*>
85*> On exit, if INFO = 0, the tridiagonal matrix T and the
86*> multipliers used to obtain the factor U or L from the
87*> factorization A = U**T*T*U or A = L*T*L**T as computed by
88*> DSYTRF.
89*> \endverbatim
90*>
91*> \param[in] LDA
92*> \verbatim
93*> LDA is INTEGER
94*> The leading dimension of the array A. LDA >= max(1,N).
95*> \endverbatim
96*>
97*> \param[out] IPIV
98*> \verbatim
99*> IPIV is INTEGER array, dimension (N)
100*> On exit, it contains the details of the interchanges, i.e.,
101*> the row and column k of A were interchanged with the
102*> row and column IPIV(k).
103*> \endverbatim
104*>
105*> \param[in,out] B
106*> \verbatim
107*> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
108*> On entry, the N-by-NRHS right hand side matrix B.
109*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
110*> \endverbatim
111*>
112*> \param[in] LDB
113*> \verbatim
114*> LDB is INTEGER
115*> The leading dimension of the array B. LDB >= max(1,N).
116*> \endverbatim
117*>
118*> \param[out] WORK
119*> \verbatim
120*> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
121*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
122*> \endverbatim
123*>
124*> \param[in] LWORK
125*> \verbatim
126*> LWORK is INTEGER
127*> The length of WORK. LWORK >= MAX(1,2*N,3*N-2), and for
128*> the best performance, LWORK >= MAX(1,N*NB), where NB is
129*> the optimal blocksize for DSYTRF_AA.
130*>
131*> If LWORK = -1, then a workspace query is assumed; the routine
132*> only calculates the optimal size of the WORK array, returns
133*> this value as the first entry of the WORK array, and no error
134*> message related to LWORK is issued by XERBLA.
135*> \endverbatim
136*>
137*> \param[out] INFO
138*> \verbatim
139*> INFO is INTEGER
140*> = 0: successful exit
141*> < 0: if INFO = -i, the i-th argument had an illegal value
142*> > 0: if INFO = i, D(i,i) is exactly zero. The factorization
143*> has been completed, but the block diagonal matrix D is
144*> exactly singular, so the solution could not be computed.
145*> \endverbatim
146*
147* Authors:
148* ========
149*
150*> \author Univ. of Tennessee
151*> \author Univ. of California Berkeley
152*> \author Univ. of Colorado Denver
153*> \author NAG Ltd.
154*
155*> \ingroup hesv_aa
156*
157* =====================================================================
158 SUBROUTINE dsysv_aa( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
159 $ LWORK, INFO )
160*
161* -- LAPACK driver routine --
162* -- LAPACK is a software package provided by Univ. of Tennessee, --
163* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
164*
165* .. Scalar Arguments ..
166 CHARACTER UPLO
167 INTEGER INFO, LDA, LDB, LWORK, N, NRHS
168* ..
169* .. Array Arguments ..
170 INTEGER IPIV( * )
171 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), WORK( * )
172* ..
173*
174* =====================================================================
175*
176* .. Local Scalars ..
177 LOGICAL LQUERY
178 INTEGER LWKMIN, LWKOPT, LWKOPT_SYTRF, LWKOPT_SYTRS
179* ..
180* .. External Functions ..
181 LOGICAL LSAME
182 INTEGER ILAENV
183 EXTERNAL ilaenv, lsame
184* ..
185* .. External Subroutines ..
186 EXTERNAL xerbla, dsytrf_aa, dsytrs_aa
187* ..
188* .. Intrinsic Functions ..
189 INTRINSIC max
190* ..
191* .. Executable Statements ..
192*
193* Test the input parameters.
194*
195 info = 0
196 lquery = ( lwork.EQ.-1 )
197 lwkmin = max( 1, 2*n, 3*n-2 )
198 IF( .NOT.lsame( uplo, 'U' ) .AND.
199 $ .NOT.lsame( uplo, 'L' ) ) THEN
200 info = -1
201 ELSE IF( n.LT.0 ) THEN
202 info = -2
203 ELSE IF( nrhs.LT.0 ) THEN
204 info = -3
205 ELSE IF( lda.LT.max( 1, n ) ) THEN
206 info = -5
207 ELSE IF( ldb.LT.max( 1, n ) ) THEN
208 info = -8
209 ELSE IF( lwork.LT.lwkmin .AND. .NOT.lquery ) THEN
210 info = -10
211 END IF
212*
213 IF( info.EQ.0 ) THEN
214 CALL dsytrf_aa( uplo, n, a, lda, ipiv, work, -1, info )
215 lwkopt_sytrf = int( work( 1 ) )
216 CALL dsytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,
217 $ -1, info )
218 lwkopt_sytrs = int( work( 1 ) )
219 lwkopt = max( lwkmin, lwkopt_sytrf, lwkopt_sytrs )
220 work( 1 ) = lwkopt
221 END IF
222*
223 IF( info.NE.0 ) THEN
224 CALL xerbla( 'DSYSV_AA ', -info )
225 RETURN
226 ELSE IF( lquery ) THEN
227 RETURN
228 END IF
229*
230* Compute the factorization A = U**T*T*U or A = L*T*L**T.
231*
232 CALL dsytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info )
233 IF( info.EQ.0 ) THEN
234*
235* Solve the system A*X = B, overwriting B with X.
236*
237 CALL dsytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,
238 $ lwork, info )
239*
240 END IF
241*
242 work( 1 ) = lwkopt
243*
244 RETURN
245*
246* End of DSYSV_AA
247*
248 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
DSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices
Definition dsysv_aa.f:160
subroutine dsytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)
DSYTRF_AA
Definition dsytrf_aa.f:133
subroutine dsytrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
DSYTRS_AA
Definition dsytrs_aa.f:135