1ZSYSV(1)              LAPACK driver routine (version 3.2)             ZSYSV(1)
2
3
4

NAME

6       ZSYSV  -  computes the solution to a complex system of linear equations
7       A * X = B,
8

SYNOPSIS

10       SUBROUTINE ZSYSV( UPLO, N, NRHS, A, LDA, IPIV,  B,  LDB,  WORK,  LWORK,
11                         INFO )
12
13           CHARACTER     UPLO
14
15           INTEGER       INFO, LDA, LDB, LWORK, N, NRHS
16
17           INTEGER       IPIV( * )
18
19           COMPLEX*16    A( LDA, * ), B( LDB, * ), WORK( * )
20

PURPOSE

22       ZSYSV computes the solution to a complex system of linear equations
23          A  * X = B, where A is an N-by-N symmetric matrix and X and B are N-
24       by-NRHS matrices.
25       The diagonal pivoting method is used to factor A as
26          A = U * D * U**T,  if UPLO = 'U', or
27          A = L * D * L**T,  if UPLO = 'L',
28       where U (or L) is a product of permutation and unit upper (lower)  tri‐
29       angular matrices, and D is symmetric and block diagonal with 1-by-1 and
30       2-by-2 diagonal blocks.  The factored form of A is then used  to  solve
31       the system of equations A * X = B.
32

ARGUMENTS

34       UPLO    (input) CHARACTER*1
35               = 'U':  Upper triangle of A is stored;
36               = 'L':  Lower triangle of A is stored.
37
38       N       (input) INTEGER
39               The  number  of linear equations, i.e., the order of the matrix
40               A.  N >= 0.
41
42       NRHS    (input) INTEGER
43               The number of right hand sides, i.e., the number of columns  of
44               the matrix B.  NRHS >= 0.
45
46       A       (input/output) COMPLEX*16 array, dimension (LDA,N)
47               On  entry,  the symmetric matrix A.  If UPLO = 'U', the leading
48               N-by-N upper triangular part of A contains the upper triangular
49               part of the matrix A, and the strictly lower triangular part of
50               A is not referenced.  If UPLO = 'L', the leading  N-by-N  lower
51               triangular  part of A contains the lower triangular part of the
52               matrix A, and the strictly upper triangular part of  A  is  not
53               referenced.   On exit, if INFO = 0, the block diagonal matrix D
54               and the multipliers used to obtain the factor U or L  from  the
55               factorization  A  =  U*D*U**T  or  A  = L*D*L**T as computed by
56               ZSYTRF.
57
58       LDA     (input) INTEGER
59               The leading dimension of the array A.  LDA >= max(1,N).
60
61       IPIV    (output) INTEGER array, dimension (N)
62               Details of the interchanges and the block structure  of  D,  as
63               determined  by ZSYTRF.  If IPIV(k) > 0, then rows and columns k
64               and IPIV(k) were interchanged, and D(k,k) is a 1-by-1  diagonal
65               block.   If  UPLO  = 'U' and IPIV(k) = IPIV(k-1) < 0, then rows
66               and  columns   k-1   and   -IPIV(k)   were   interchanged   and
67               D(k-1:k,k-1:k)  is  a 2-by-2 diagonal block.  If UPLO = 'L' and
68               IPIV(k) = IPIV(k+1) < 0, then rows and columns k+1 and -IPIV(k)
69               were  interchanged  and  D(k:k+1,k:k+1)  is  a  2-by-2 diagonal
70               block.
71
72       B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
73               On entry, the N-by-NRHS right hand side matrix B.  On exit,  if
74               INFO = 0, the N-by-NRHS solution matrix X.
75
76       LDB     (input) INTEGER
77               The leading dimension of the array B.  LDB >= max(1,N).
78
79       WORK    (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
80               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
81
82       LWORK   (input) INTEGER
83               The length of WORK.  LWORK >= 1, and for best performance LWORK
84               >= max(1,N*NB), where NB is the optimal blocksize  for  ZSYTRF.
85               If  LWORK  = -1, then a workspace query is assumed; the routine
86               only calculates the optimal size of  the  WORK  array,  returns
87               this  value  as the first entry of the WORK array, and no error
88               message related to LWORK is issued by XERBLA.
89
90       INFO    (output) INTEGER
91               = 0: successful exit
92               < 0: if INFO = -i, the i-th argument had an illegal value
93               > 0: if INFO = i, D(i,i) is exactly  zero.   The  factorization
94               has  been completed, but the block diagonal matrix D is exactly
95               singular, so the solution could not be computed.
96
97
98
99 LAPACK driver routine (version 3.N2o)vember 2008                        ZSYSV(1)
Impressum