LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zsysv_aa_2stage()

subroutine zsysv_aa_2stage ( character uplo,
integer n,
integer nrhs,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( * ) tb,
integer ltb,
integer, dimension( * ) ipiv,
integer, dimension( * ) ipiv2,
complex*16, dimension( ldb, * ) b,
integer ldb,
complex*16, dimension( * ) work,
integer lwork,
integer info )

ZSYSV_AA_2STAGE computes the solution to system of linear equations A * X = B for SY matrices

Download ZSYSV_AA_2STAGE + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZSYSV_AA_2STAGE computes the solution to a complex system of
!> linear equations
!>    A * X = B,
!> where A is an N-by-N symmetric matrix and X and B are N-by-NRHS
!> matrices.
!>
!> Aasen's 2-stage algorithm is used to factor A as
!>    A = U**T * T * U,  if UPLO = 'U', or
!>    A = L * T * L**T,  if UPLO = 'L',
!> where U (or L) is a product of permutation and unit upper (lower)
!> triangular matrices, and T is symmetric and band. The matrix T is
!> then LU-factored with partial pivoting. The factored form of A
!> is then used to solve the system of equations A * X = B.
!>
!> This is the blocked version of the algorithm, calling Level 3 BLAS.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  Upper triangle of A is stored;
!>          = 'L':  Lower triangle of A is stored.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]NRHS
!>          NRHS is INTEGER
!>          The number of right hand sides, i.e., the number of columns
!>          of the matrix B.  NRHS >= 0.
!> 
[in,out]A
!>          A is COMPLEX*16 array, dimension (LDA,N)
!>          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
!>          N-by-N upper triangular part of A contains the upper
!>          triangular part of the matrix A, and the strictly lower
!>          triangular part of A is not referenced.  If UPLO = 'L', the
!>          leading N-by-N lower triangular part of A contains the lower
!>          triangular part of the matrix A, and the strictly upper
!>          triangular part of A is not referenced.
!>
!>          On exit, L is stored below (or above) the subdiagonal blocks,
!>          when UPLO  is 'L' (or 'U').
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[out]TB
!>          TB is COMPLEX*16 array, dimension (LTB)
!>          On exit, details of the LU factorization of the band matrix.
!> 
[in]LTB
!>          LTB is INTEGER
!>          The size of the array TB. LTB >= 4*N, internally
!>          used to select NB such that LTB >= (3*NB+1)*N.
!>
!>          If LTB = -1, then a workspace query is assumed; the
!>          routine only calculates the optimal size of LTB, 
!>          returns this value as the first entry of TB, and
!>          no error message related to LTB is issued by XERBLA.
!> 
[out]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          On exit, it contains the details of the interchanges, i.e.,
!>          the row and column k of A were interchanged with the
!>          row and column IPIV(k).
!> 
[out]IPIV2
!>          IPIV2 is INTEGER array, dimension (N)
!>          On exit, it contains the details of the interchanges, i.e.,
!>          the row and column k of T were interchanged with the
!>          row and column IPIV(k).
!> 
[in,out]B
!>          B is COMPLEX*16 array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, the solution matrix X.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
[out]WORK
!>          WORK is COMPLEX*16 workspace of size LWORK
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The size of WORK. LWORK >= N, internally used to select NB
!>          such that LWORK >= N*NB.
!>
!>          If LWORK = -1, then a workspace query is assumed; the
!>          routine only calculates the optimal size of the WORK array,
!>          returns this value as the first entry of the WORK array, and
!>          no error message related to LWORK is issued by XERBLA.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value.
!>          > 0:  if INFO = i, band LU factorization failed on i-th column
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 181 of file zsysv_aa_2stage.f.

184*
185* -- LAPACK computational routine --
186* -- LAPACK is a software package provided by Univ. of Tennessee, --
187* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
188*
189 IMPLICIT NONE
190*
191* .. Scalar Arguments ..
192 CHARACTER UPLO
193 INTEGER N, NRHS, LDA, LDB, LTB, LWORK, INFO
194* ..
195* .. Array Arguments ..
196 INTEGER IPIV( * ), IPIV2( * )
197 COMPLEX*16 A( LDA, * ), B( LDB, * ), TB( * ), WORK( * )
198* ..
199*
200* =====================================================================
201*
202* .. Local Scalars ..
203 LOGICAL UPPER, TQUERY, WQUERY
204 INTEGER LWKOPT
205* ..
206* .. External Functions ..
207 LOGICAL LSAME
208 EXTERNAL lsame
209* ..
210* .. External Subroutines ..
211 EXTERNAL xerbla, zsytrf_aa_2stage,
213* ..
214* .. Intrinsic Functions ..
215 INTRINSIC max
216* ..
217* .. Executable Statements ..
218*
219* Test the input parameters.
220*
221 info = 0
222 upper = lsame( uplo, 'U' )
223 wquery = ( lwork.EQ.-1 )
224 tquery = ( ltb.EQ.-1 )
225 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
226 info = -1
227 ELSE IF( n.LT.0 ) THEN
228 info = -2
229 ELSE IF( nrhs.LT.0 ) THEN
230 info = -3
231 ELSE IF( lda.LT.max( 1, n ) ) THEN
232 info = -5
233 ELSE IF( ltb.LT.( 4*n ) .AND. .NOT.tquery ) THEN
234 info = -7
235 ELSE IF( ldb.LT.max( 1, n ) ) THEN
236 info = -11
237 ELSE IF( lwork.LT.n .AND. .NOT.wquery ) THEN
238 info = -13
239 END IF
240*
241 IF( info.EQ.0 ) THEN
242 CALL zsytrf_aa_2stage( uplo, n, a, lda, tb, -1, ipiv,
243 $ ipiv2, work, -1, info )
244 lwkopt = int( work(1) )
245 END IF
246*
247 IF( info.NE.0 ) THEN
248 CALL xerbla( 'ZSYSV_AA_2STAGE', -info )
249 RETURN
250 ELSE IF( wquery .OR. tquery ) THEN
251 RETURN
252 END IF
253*
254*
255* Compute the factorization A = U**T*T*U or A = L*T*L**T.
256*
257 CALL zsytrf_aa_2stage( uplo, n, a, lda, tb, ltb, ipiv, ipiv2,
258 $ work, lwork, info )
259 IF( info.EQ.0 ) THEN
260*
261* Solve the system A*X = B, overwriting B with X.
262*
263 CALL zsytrs_aa_2stage( uplo, n, nrhs, a, lda, tb, ltb, ipiv,
264 $ ipiv2, b, ldb, info )
265*
266 END IF
267*
268 work( 1 ) = lwkopt
269*
270* End of ZSYSV_AA_2STAGE
271*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zsytrf_aa_2stage(uplo, n, a, lda, tb, ltb, ipiv, ipiv2, work, lwork, info)
ZSYTRF_AA_2STAGE
subroutine zsytrs_aa_2stage(uplo, n, nrhs, a, lda, tb, ltb, ipiv, ipiv2, b, ldb, info)
ZSYTRS_AA_2STAGE
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: