1DSPOSV(1)       LAPACK PROTOTYPE driver routine (version 3.1.2)      DSPOSV(1)
2
3
4

NAME

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

SYNOPSIS

10       SUBROUTINE DSPOSV( UPLO, N, NRHS, A, LDA, B, LDB, X, LDX, WORK,
11
12           +              SWORK, ITER, INFO )
13
14           CHARACTER      UPLO
15
16           INTEGER        INFO, ITER, LDA, LDB, LDX, N, NRHS
17
18           REAL           SWORK( * )
19
20           DOUBLE         PRECISION A( LDA, * ), B( LDB, * ), WORK( N, * ),
21
22           +              X( LDX, * )
23

PURPOSE

25       DSPOSV computes the solution to a real system of linear equations
26          A * X = B, where A is an N-by-N symmetric positive  definite  matrix
27       and X and B are N-by-NRHS matrices.
28       DSPOSV  first  attempts to factorize the matrix in SINGLE PRECISION and
29       use this factorization within an iterative refinement procedure to pro‐
30       duce  a  solution with DOUBLE PRECISION normwise backward error quality
31       (see below). If the approach fails the method switches to a DOUBLE PRE‐
32       CISION factorization and solve.
33       The  iterative  refinement is not going to be a winning strategy if the
34       ratio SINGLE PRECISION performance over DOUBLE PRECISION performance is
35       too  small.  A reasonable strategy should take the number of right-hand
36       sides and the size of the matrix into account.  This might be done with
37       a  call  to  ILAENV  in  the future. Up to now, we always try iterative
38       refinement.
39       The iterative refinement process is stopped if
40           ITER > ITERMAX
41       or for all the RHS we have:
42           RNRM < SQRT(N)*XNRM*ANRM*EPS*BWDMAX
43       where
44           o ITER is the number of the current iteration in the iterative
45             refinement process
46           o RNRM is the infinity-norm of the residual
47           o XNRM is the infinity-norm of the solution
48           o ANRM is the infinity-operator-norm of the matrix A
49           o EPS is the machine  epsilon  returned  by  DLAMCH('Epsilon')  The
50       value ITERMAX and BWDMAX are fixed to 30 and 1.0D+00
51       respectively.
52

ARGUMENTS

54       UPLO    (input) CHARACTER
55               = 'U':  Upper triangle of A is stored;
56               = 'L':  Lower triangle of A is stored.
57
58       N       (input) INTEGER
59               The  number  of linear equations, i.e., the order of the matrix
60               A.  N >= 0.
61
62       NRHS    (input) INTEGER
63               The number of right hand sides, i.e., the number of columns  of
64               the matrix B.  NRHS >= 0.
65
66       A       (input or input/ouptut) DOUBLE PRECISION array,
67               dimension  (LDA,N) On entry, the symmetric matrix A.  If UPLO =
68               'U', the leading N-by-N upper triangular part of A contains the
69               upper  triangular  part of the matrix A, and the strictly lower
70               triangular part of A is not referenced.  If  UPLO  =  'L',  the
71               leading  N-by-N  lower  triangular part of A contains the lower
72               triangular part of the matrix A, and the strictly upper  trian‐
73               gular  part  of  A  is  not  referenced.  On exit, if iterative
74               refinement has been successfully used (INFO.EQ.0 and ITER.GE.0,
75               see  description  below), then A is unchanged, if double preci‐
76               sion factorization has been used (INFO.EQ.0 and ITER.LT.0,  see
77               description below), then the array A contains the factor U or L
78               from the Cholesky factorization A = U**T*U or A = L*L**T.
79
80       LDA     (input) INTEGER
81               The leading dimension of the array A.  LDA >= max(1,N).
82
83       B       (input) DOUBLE PRECISION array, dimension (LDB,NRHS)
84               The N-by-NRHS right hand side matrix B.
85
86       LDB     (input) INTEGER
87               The leading dimension of the array B.  LDB >= max(1,N).
88
89       X       (output) DOUBLE PRECISION array, dimension (LDX,NRHS)
90               If INFO = 0, the N-by-NRHS solution matrix X.
91
92       LDX     (input) INTEGER
93               The leading dimension of the array X.  LDX >= max(1,N).
94
95       WORK    (workspace) DOUBLE PRECISION array, dimension (N*NRHS)
96               This array is used to hold the residual vectors.
97
98       SWORK   (workspace) REAL array, dimension (N*(N+NRHS))
99               This array is used to use the single precision matrix  and  the
100               right-hand sides or solutions in single precision.
101
102       ITER    (output) INTEGER
103               <  0: iterative refinement has failed, double precision factor‐
104               ization has been performed -1 : the routine fell back  to  full
105               precision  for implementation- or machine-specific reasons -2 :
106               narrowing the precision induced an overflow, the  routine  fell
107               back to full precision -3 : failure of SPOTRF
108               -31:  stop the iterative refinement after the 30th iterations >
109               0: iterative refinement has been sucessfully used.  Returns the
110               number of iterations
111
112       INFO    (output) INTEGER
113               = 0:  successful exit
114               < 0:  if INFO = -i, the i-th argument had an illegal value
115               > 0:  if INFO = i, the leading minor of order i of (DOUBLE PRE‐
116               CISION) A is not positive definite, so the factorization  could
117               not  be  completed,  and  the  solution  has not been computed.
118               =========
119
120
121
122 LAPACK PROTOTYPE driver routine (Nvoevresmiboenr 32.010.82)                     DSPOSV(1)
Impressum