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

◆ zhesv_aa_2stage()

subroutine zhesv_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 )

ZHESV_AA_2STAGE computes the solution to system of linear equations A * X = B for HE matrices

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

Purpose:
!>
!> ZHESV_AA_2STAGE computes the solution to a complex system of 
!> linear equations
!>    A * X = B,
!> where A is an N-by-N Hermitian matrix and X and B are N-by-NRHS
!> matrices.
!>
!> Aasen's 2-stage algorithm is used to factor A as
!>    A = U**H * T * U,  if UPLO = 'U', or
!>    A = L * T * L**H,  if UPLO = 'L',
!> where U (or L) is a product of permutation and unit upper (lower)
!> triangular matrices, and T is Hermitian 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 hermitian 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 (MAX(1,LTB)).
!>          On exit, details of the LU factorization of the band matrix.
!> 
[in]LTB
!>          LTB is INTEGER
!>          The size of the array TB. LTB >= MAX(1,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 (MAX(1,LWORK)).
!>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The size of WORK. LWORK >= MAX(1,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 183 of file zhesv_aa_2stage.f.

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 COMPLEX*16 A( LDA, * ), B( LDB, * ), TB( * ), WORK( * )
200* ..
201*
202* =====================================================================
203* .. Parameters ..
204 COMPLEX*16 ZERO, ONE
205 parameter( zero = ( 0.0d+0, 0.0d+0 ),
206 $ one = ( 1.0d+0, 0.0d+0 ) )
207*
208* .. Local Scalars ..
209 LOGICAL UPPER, TQUERY, WQUERY
210 INTEGER LWKOPT, LWKMIN
211* ..
212* .. External Functions ..
213 LOGICAL LSAME
214 INTEGER ILAENV
215 EXTERNAL lsame, ilaenv
216* ..
217* .. External Subroutines ..
218 EXTERNAL xerbla, zhetrf_aa_2stage,
220* ..
221* .. Intrinsic Functions ..
222 INTRINSIC max
223* ..
224* .. Executable Statements ..
225*
226* Test the input parameters.
227*
228 info = 0
229 upper = lsame( uplo, 'U' )
230 wquery = ( lwork.EQ.-1 )
231 tquery = ( ltb.EQ.-1 )
232 lwkmin = max( 1, n )
233 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
234 info = -1
235 ELSE IF( n.LT.0 ) THEN
236 info = -2
237 ELSE IF( nrhs.LT.0 ) THEN
238 info = -3
239 ELSE IF( lda.LT.max( 1, n ) ) THEN
240 info = -5
241 ELSE IF( ltb.LT.max( 1, 4*n ) .AND. .NOT.tquery ) THEN
242 info = -7
243 ELSE IF( ldb.LT.max( 1, n ) ) THEN
244 info = -11
245 ELSE IF( lwork.LT.lwkmin .AND. .NOT.wquery ) THEN
246 info = -13
247 END IF
248*
249 IF( info.EQ.0 ) THEN
250 CALL zhetrf_aa_2stage( uplo, n, a, lda, tb, -1, ipiv,
251 $ ipiv2, work, -1, info )
252 lwkopt = max( lwkmin, int( work( 1 ) ) )
253 work( 1 ) = lwkopt
254 END IF
255*
256 IF( info.NE.0 ) THEN
257 CALL xerbla( 'ZHESV_AA_2STAGE', -info )
258 RETURN
259 ELSE IF( wquery .OR. tquery ) THEN
260 RETURN
261 END IF
262*
263* Compute the factorization A = U**H*T*U or A = L*T*L**H.
264*
265 CALL zhetrf_aa_2stage( uplo, n, a, lda, tb, ltb, ipiv, ipiv2,
266 $ work, lwork, info )
267 IF( info.EQ.0 ) THEN
268*
269* Solve the system A*X = B, overwriting B with X.
270*
271 CALL zhetrs_aa_2stage( uplo, n, nrhs, a, lda, tb, ltb, ipiv,
272 $ ipiv2, b, ldb, info )
273*
274 END IF
275*
276 work( 1 ) = lwkopt
277*
278 RETURN
279*
280* End of ZHESV_AA_2STAGE
281*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zhetrf_aa_2stage(uplo, n, a, lda, tb, ltb, ipiv, ipiv2, work, lwork, info)
ZHETRF_AA_2STAGE
subroutine zhetrs_aa_2stage(uplo, n, nrhs, a, lda, tb, ltb, ipiv, ipiv2, b, ldb, info)
ZHETRS_AA_2STAGE
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:160
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: