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

NAME

6       SSYSVX  - uses the diagonal pivoting factorization to compute the solu‐
7       tion to a real system of linear equations A * X = B,
8

SYNOPSIS

10       SUBROUTINE SSYSVX( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB,
11                          X,  LDX, RCOND, FERR, BERR, WORK, LWORK, IWORK, INFO
12                          )
13
14           CHARACTER      FACT, UPLO
15
16           INTEGER        INFO, LDA, LDAF, LDB, LDX, LWORK, N, NRHS
17
18           REAL           RCOND
19
20           INTEGER        IPIV( * ), IWORK( * )
21
22           REAL           A( LDA, * ), AF( LDAF, * ), B( LDB, * ), BERR( *  ),
23                          FERR( * ), WORK( * ), X( LDX, * )
24

PURPOSE

26       SSYSVX uses the diagonal pivoting factorization to compute the solution
27       to a real system of linear equations A * X = B, where A  is  an  N-by-N
28       symmetric matrix and X and B are N-by-NRHS matrices.
29       Error  bounds  on  the  solution and a condition estimate are also pro‐
30       vided.
31

DESCRIPTION

33       The following steps are performed:
34       1. If FACT = 'N', the diagonal pivoting method is used to factor A.
35          The form of the factorization is
36             A = U * D * U**T,  if UPLO = 'U', or
37             A = L * D * L**T,  if UPLO = 'L',
38          where U (or L) is a product of permutation and unit upper (lower)
39          triangular matrices, and D is symmetric and block diagonal with
40          1-by-1 and 2-by-2 diagonal blocks.
41       2. If some D(i,i)=0, so that D is exactly singular, then the routine
42          returns with INFO = i. Otherwise, the factored form of A is used
43          to estimate the condition number of the matrix A.  If the
44          reciprocal of the condition number is less than machine precision,
45          INFO = N+1 is returned as a warning, but the routine still goes on
46          to solve for X and compute error bounds as described below.  3.  The
47       system of equations is solved for X using the factored form
48          of A.
49       4. Iterative refinement is applied to improve the computed solution
50          matrix and calculate error bounds and backward error estimates
51          for it.
52

ARGUMENTS

54       FACT    (input) CHARACTER*1
55               Specifies  whether  or not the factored form of A has been sup‐
56               plied on entry.  = 'F':  On entry, AF and IPIV contain the fac‐
57               tored  form  of  A.   AF and IPIV will not be modified.  = 'N':
58               The matrix A will be copied to AF and factored.
59
60       UPLO    (input) CHARACTER*1
61               = 'U':  Upper triangle of A is stored;
62               = 'L':  Lower triangle of A is stored.
63
64       N       (input) INTEGER
65               The number of linear equations, i.e., the order of  the  matrix
66               A.  N >= 0.
67
68       NRHS    (input) INTEGER
69               The  number of right hand sides, i.e., the number of columns of
70               the matrices B and X.  NRHS >= 0.
71
72       A       (input) REAL array, dimension (LDA,N)
73               The symmetric matrix A.  If UPLO  =  'U',  the  leading  N-by-N
74               upper  triangular  part of A contains the upper triangular part
75               of the matrix A, and the strictly lower triangular part of A is
76               not referenced.  If UPLO = 'L', the leading N-by-N lower trian‐
77               gular part of A contains  the  lower  triangular  part  of  the
78               matrix  A,  and  the strictly upper triangular part of A is not
79               referenced.
80
81       LDA     (input) INTEGER
82               The leading dimension of the array A.  LDA >= max(1,N).
83
84       AF      (input or output) REAL array, dimension (LDAF,N)
85               If FACT = 'F', then AF is an input argument and on  entry  con‐
86               tains  the  block diagonal matrix D and the multipliers used to
87               obtain the factor U or L from the factorization A = U*D*U**T or
88               A  = L*D*L**T as computed by SSYTRF.  If FACT = 'N', then AF is
89               an output argument and  on  exit  returns  the  block  diagonal
90               matrix  D  and the multipliers used to obtain the factor U or L
91               from the factorization A = U*D*U**T or A = L*D*L**T.
92
93       LDAF    (input) INTEGER
94               The leading dimension of the array AF.  LDAF >= max(1,N).
95
96       IPIV    (input or output) INTEGER array, dimension (N)
97               If FACT = 'F', then IPIV is an input argument and on entry con‐
98               tains details of the interchanges and the block structure of D,
99               as determined by SSYTRF.  If IPIV(k) > 0, then rows and columns
100               k and IPIV(k) were interchanged and D(k,k) is a 1-by-1 diagonal
101               block.  If UPLO = 'U' and IPIV(k) = IPIV(k-1) <  0,  then  rows
102               and   columns   k-1   and   -IPIV(k)   were   interchanged  and
103               D(k-1:k,k-1:k) is a 2-by-2 diagonal block.  If UPLO =  'L'  and
104               IPIV(k) = IPIV(k+1) < 0, then rows and columns k+1 and -IPIV(k)
105               were interchanged  and  D(k:k+1,k:k+1)  is  a  2-by-2  diagonal
106               block.   If  FACT = 'N', then IPIV is an output argument and on
107               exit contains details of the interchanges and the block  struc‐
108               ture of D, as determined by SSYTRF.
109
110       B       (input) REAL array, dimension (LDB,NRHS)
111               The N-by-NRHS right hand side matrix B.
112
113       LDB     (input) INTEGER
114               The leading dimension of the array B.  LDB >= max(1,N).
115
116       X       (output) REAL array, dimension (LDX,NRHS)
117               If INFO = 0 or INFO = N+1, the N-by-NRHS solution matrix X.
118
119       LDX     (input) INTEGER
120               The leading dimension of the array X.  LDX >= max(1,N).
121
122       RCOND   (output) REAL
123               The  estimate  of the reciprocal condition number of the matrix
124               A.  If RCOND is less than the machine precision (in particular,
125               if  RCOND  =  0),  the matrix is singular to working precision.
126               This condition is indicated by a return code of INFO > 0.
127
128       FERR    (output) REAL array, dimension (NRHS)
129               The estimated forward error bound for each solution vector X(j)
130               (the  j-th  column  of the solution matrix X).  If XTRUE is the
131               true solution corresponding to X(j), FERR(j)  is  an  estimated
132               upper bound for the magnitude of the largest element in (X(j) -
133               XTRUE) divided by the magnitude of the largest element in X(j).
134               The  estimate  is as reliable as the estimate for RCOND, and is
135               almost always a slight overestimate of the true error.
136
137       BERR    (output) REAL array, dimension (NRHS)
138               The componentwise relative backward error of each solution vec‐
139               tor  X(j) (i.e., the smallest relative change in any element of
140               A or B that makes X(j) an exact solution).
141
142       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
143               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
144
145       LWORK   (input) INTEGER
146               The length of WORK.  LWORK >= max(1,3*N), and for best  perfor‐
147               mance,  when  FACT = 'N', LWORK >= max(1,3*N,N*NB), where NB is
148               the optimal blocksize for  SSYTRF.   If  LWORK  =  -1,  then  a
149               workspace  query  is  assumed;  the routine only calculates the
150               optimal size of the WORK array, returns this value as the first
151               entry  of the WORK array, and no error message related to LWORK
152               is issued by XERBLA.
153
154       IWORK   (workspace) INTEGER array, dimension (N)
155
156       INFO    (output) INTEGER
157               = 0: successful exit
158               < 0: if INFO = -i, the i-th argument had an illegal value
159               > 0: if INFO = i, and i is
160               <= N:  D(i,i) is exactly zero.  The factorization has been com‐
161               pleted  but  the  factor D is exactly singular, so the solution
162               and error bounds could not be computed. RCOND = 0 is  returned.
163               =  N+1: D is nonsingular, but RCOND is less than machine preci‐
164               sion, meaning that the matrix is singular to working precision.
165               Nevertheless,  the  solution  and  error  bounds  are  computed
166               because there are a number of  situations  where  the  computed
167               solution  can  be  more  accurate than the value of RCOND would
168               suggest.
169
170
171
172 LAPACK driver routine (version 3.N2o)vember 2008                       SSYSVX(1)
Impressum