Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / ssyrfsx.f
1 *> \brief \b SSYRFSX
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SSYRFSX + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssyrfsx.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssyrfsx.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssyrfsx.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE SSYRFSX( UPLO, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV,
22 *                           S, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS,
23 *                           ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS,
24 *                           WORK, IWORK, INFO )
25 *
26 *       .. Scalar Arguments ..
27 *       CHARACTER          UPLO, EQUED
28 *       INTEGER            INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
29 *      $                   N_ERR_BNDS
30 *       REAL               RCOND
31 *       ..
32 *       .. Array Arguments ..
33 *       INTEGER            IPIV( * ), IWORK( * )
34 *       REAL               A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
35 *      $                   X( LDX, * ), WORK( * )
36 *       REAL               S( * ), PARAMS( * ), BERR( * ),
37 *      $                   ERR_BNDS_NORM( NRHS, * ),
38 *      $                   ERR_BNDS_COMP( NRHS, * )
39 *       ..
40 *
41 *
42 *> \par Purpose:
43 *  =============
44 *>
45 *> \verbatim
46 *>
47 *>    SSYRFSX improves the computed solution to a system of linear
48 *>    equations when the coefficient matrix is symmetric indefinite, and
49 *>    provides error bounds and backward error estimates for the
50 *>    solution.  In addition to normwise error bound, the code provides
51 *>    maximum componentwise error bound if possible.  See comments for
52 *>    ERR_BNDS_NORM and ERR_BNDS_COMP for details of the error bounds.
53 *>
54 *>    The original system of linear equations may have been equilibrated
55 *>    before calling this routine, as described by arguments EQUED and S
56 *>    below. In this case, the solution and error bounds returned are
57 *>    for the original unequilibrated system.
58 *> \endverbatim
59 *
60 *  Arguments:
61 *  ==========
62 *
63 *> \verbatim
64 *>     Some optional parameters are bundled in the PARAMS array.  These
65 *>     settings determine how refinement is performed, but often the
66 *>     defaults are acceptable.  If the defaults are acceptable, users
67 *>     can pass NPARAMS = 0 which prevents the source code from accessing
68 *>     the PARAMS argument.
69 *> \endverbatim
70 *>
71 *> \param[in] UPLO
72 *> \verbatim
73 *>          UPLO is CHARACTER*1
74 *>       = 'U':  Upper triangle of A is stored;
75 *>       = 'L':  Lower triangle of A is stored.
76 *> \endverbatim
77 *>
78 *> \param[in] EQUED
79 *> \verbatim
80 *>          EQUED is CHARACTER*1
81 *>     Specifies the form of equilibration that was done to A
82 *>     before calling this routine. This is needed to compute
83 *>     the solution and error bounds correctly.
84 *>       = 'N':  No equilibration
85 *>       = 'Y':  Both row and column equilibration, i.e., A has been
86 *>               replaced by diag(S) * A * diag(S).
87 *>               The right hand side B has been changed accordingly.
88 *> \endverbatim
89 *>
90 *> \param[in] N
91 *> \verbatim
92 *>          N is INTEGER
93 *>     The order of the matrix A.  N >= 0.
94 *> \endverbatim
95 *>
96 *> \param[in] NRHS
97 *> \verbatim
98 *>          NRHS is INTEGER
99 *>     The number of right hand sides, i.e., the number of columns
100 *>     of the matrices B and X.  NRHS >= 0.
101 *> \endverbatim
102 *>
103 *> \param[in] A
104 *> \verbatim
105 *>          A is REAL array, dimension (LDA,N)
106 *>     The symmetric matrix A.  If UPLO = 'U', the leading N-by-N
107 *>     upper triangular part of A contains the upper triangular
108 *>     part of the matrix A, and the strictly lower triangular
109 *>     part of A is not referenced.  If UPLO = 'L', the leading
110 *>     N-by-N lower triangular part of A contains the lower
111 *>     triangular part of the matrix A, and the strictly upper
112 *>     triangular part of A is not referenced.
113 *> \endverbatim
114 *>
115 *> \param[in] LDA
116 *> \verbatim
117 *>          LDA is INTEGER
118 *>     The leading dimension of the array A.  LDA >= max(1,N).
119 *> \endverbatim
120 *>
121 *> \param[in] AF
122 *> \verbatim
123 *>          AF is REAL array, dimension (LDAF,N)
124 *>     The factored form of the matrix A.  AF contains the block
125 *>     diagonal matrix D and the multipliers used to obtain the
126 *>     factor U or L from the factorization A = U*D*U**T or A =
127 *>     L*D*L**T as computed by SSYTRF.
128 *> \endverbatim
129 *>
130 *> \param[in] LDAF
131 *> \verbatim
132 *>          LDAF is INTEGER
133 *>     The leading dimension of the array AF.  LDAF >= max(1,N).
134 *> \endverbatim
135 *>
136 *> \param[in] IPIV
137 *> \verbatim
138 *>          IPIV is INTEGER array, dimension (N)
139 *>     Details of the interchanges and the block structure of D
140 *>     as determined by SSYTRF.
141 *> \endverbatim
142 *>
143 *> \param[in,out] S
144 *> \verbatim
145 *>          S is REAL array, dimension (N)
146 *>     The scale factors for A.  If EQUED = 'Y', A is multiplied on
147 *>     the left and right by diag(S).  S is an input argument if FACT =
148 *>     'F'; otherwise, S is an output argument.  If FACT = 'F' and EQUED
149 *>     = 'Y', each element of S must be positive.  If S is output, each
150 *>     element of S is a power of the radix. If S is input, each element
151 *>     of S should be a power of the radix to ensure a reliable solution
152 *>     and error estimates. Scaling by powers of the radix does not cause
153 *>     rounding errors unless the result underflows or overflows.
154 *>     Rounding errors during scaling lead to refining with a matrix that
155 *>     is not equivalent to the input matrix, producing error estimates
156 *>     that may not be reliable.
157 *> \endverbatim
158 *>
159 *> \param[in] B
160 *> \verbatim
161 *>          B is REAL array, dimension (LDB,NRHS)
162 *>     The right hand side matrix B.
163 *> \endverbatim
164 *>
165 *> \param[in] LDB
166 *> \verbatim
167 *>          LDB is INTEGER
168 *>     The leading dimension of the array B.  LDB >= max(1,N).
169 *> \endverbatim
170 *>
171 *> \param[in,out] X
172 *> \verbatim
173 *>          X is REAL array, dimension (LDX,NRHS)
174 *>     On entry, the solution matrix X, as computed by SGETRS.
175 *>     On exit, the improved solution matrix X.
176 *> \endverbatim
177 *>
178 *> \param[in] LDX
179 *> \verbatim
180 *>          LDX is INTEGER
181 *>     The leading dimension of the array X.  LDX >= max(1,N).
182 *> \endverbatim
183 *>
184 *> \param[out] RCOND
185 *> \verbatim
186 *>          RCOND is REAL
187 *>     Reciprocal scaled condition number.  This is an estimate of the
188 *>     reciprocal Skeel condition number of the matrix A after
189 *>     equilibration (if done).  If this is less than the machine
190 *>     precision (in particular, if it is zero), the matrix is singular
191 *>     to working precision.  Note that the error may still be small even
192 *>     if this number is very small and the matrix appears ill-
193 *>     conditioned.
194 *> \endverbatim
195 *>
196 *> \param[out] BERR
197 *> \verbatim
198 *>          BERR is REAL array, dimension (NRHS)
199 *>     Componentwise relative backward error.  This is the
200 *>     componentwise relative backward error of each solution vector X(j)
201 *>     (i.e., the smallest relative change in any element of A or B that
202 *>     makes X(j) an exact solution).
203 *> \endverbatim
204 *>
205 *> \param[in] N_ERR_BNDS
206 *> \verbatim
207 *>          N_ERR_BNDS is INTEGER
208 *>     Number of error bounds to return for each right hand side
209 *>     and each type (normwise or componentwise).  See ERR_BNDS_NORM and
210 *>     ERR_BNDS_COMP below.
211 *> \endverbatim
212 *>
213 *> \param[out] ERR_BNDS_NORM
214 *> \verbatim
215 *>          ERR_BNDS_NORM is REAL array, dimension (NRHS, N_ERR_BNDS)
216 *>     For each right-hand side, this array contains information about
217 *>     various error bounds and condition numbers corresponding to the
218 *>     normwise relative error, which is defined as follows:
219 *>
220 *>     Normwise relative error in the ith solution vector:
221 *>             max_j (abs(XTRUE(j,i) - X(j,i)))
222 *>            ------------------------------
223 *>                  max_j abs(X(j,i))
224 *>
225 *>     The array is indexed by the type of error information as described
226 *>     below. There currently are up to three pieces of information
227 *>     returned.
228 *>
229 *>     The first index in ERR_BNDS_NORM(i,:) corresponds to the ith
230 *>     right-hand side.
231 *>
232 *>     The second index in ERR_BNDS_NORM(:,err) contains the following
233 *>     three fields:
234 *>     err = 1 "Trust/don't trust" boolean. Trust the answer if the
235 *>              reciprocal condition number is less than the threshold
236 *>              sqrt(n) * slamch('Epsilon').
237 *>
238 *>     err = 2 "Guaranteed" error bound: The estimated forward error,
239 *>              almost certainly within a factor of 10 of the true error
240 *>              so long as the next entry is greater than the threshold
241 *>              sqrt(n) * slamch('Epsilon'). This error bound should only
242 *>              be trusted if the previous boolean is true.
243 *>
244 *>     err = 3  Reciprocal condition number: Estimated normwise
245 *>              reciprocal condition number.  Compared with the threshold
246 *>              sqrt(n) * slamch('Epsilon') to determine if the error
247 *>              estimate is "guaranteed". These reciprocal condition
248 *>              numbers are 1 / (norm(Z^{-1},inf) * norm(Z,inf)) for some
249 *>              appropriately scaled matrix Z.
250 *>              Let Z = S*A, where S scales each row by a power of the
251 *>              radix so all absolute row sums of Z are approximately 1.
252 *>
253 *>     See Lapack Working Note 165 for further details and extra
254 *>     cautions.
255 *> \endverbatim
256 *>
257 *> \param[out] ERR_BNDS_COMP
258 *> \verbatim
259 *>          ERR_BNDS_COMP is REAL array, dimension (NRHS, N_ERR_BNDS)
260 *>     For each right-hand side, this array contains information about
261 *>     various error bounds and condition numbers corresponding to the
262 *>     componentwise relative error, which is defined as follows:
263 *>
264 *>     Componentwise relative error in the ith solution vector:
265 *>                    abs(XTRUE(j,i) - X(j,i))
266 *>             max_j ----------------------
267 *>                         abs(X(j,i))
268 *>
269 *>     The array is indexed by the right-hand side i (on which the
270 *>     componentwise relative error depends), and the type of error
271 *>     information as described below. There currently are up to three
272 *>     pieces of information returned for each right-hand side. If
273 *>     componentwise accuracy is not requested (PARAMS(3) = 0.0), then
274 *>     ERR_BNDS_COMP is not accessed.  If N_ERR_BNDS .LT. 3, then at most
275 *>     the first (:,N_ERR_BNDS) entries are returned.
276 *>
277 *>     The first index in ERR_BNDS_COMP(i,:) corresponds to the ith
278 *>     right-hand side.
279 *>
280 *>     The second index in ERR_BNDS_COMP(:,err) contains the following
281 *>     three fields:
282 *>     err = 1 "Trust/don't trust" boolean. Trust the answer if the
283 *>              reciprocal condition number is less than the threshold
284 *>              sqrt(n) * slamch('Epsilon').
285 *>
286 *>     err = 2 "Guaranteed" error bound: The estimated forward error,
287 *>              almost certainly within a factor of 10 of the true error
288 *>              so long as the next entry is greater than the threshold
289 *>              sqrt(n) * slamch('Epsilon'). This error bound should only
290 *>              be trusted if the previous boolean is true.
291 *>
292 *>     err = 3  Reciprocal condition number: Estimated componentwise
293 *>              reciprocal condition number.  Compared with the threshold
294 *>              sqrt(n) * slamch('Epsilon') to determine if the error
295 *>              estimate is "guaranteed". These reciprocal condition
296 *>              numbers are 1 / (norm(Z^{-1},inf) * norm(Z,inf)) for some
297 *>              appropriately scaled matrix Z.
298 *>              Let Z = S*(A*diag(x)), where x is the solution for the
299 *>              current right-hand side and S scales each row of
300 *>              A*diag(x) by a power of the radix so all absolute row
301 *>              sums of Z are approximately 1.
302 *>
303 *>     See Lapack Working Note 165 for further details and extra
304 *>     cautions.
305 *> \endverbatim
306 *>
307 *> \param[in] NPARAMS
308 *> \verbatim
309 *>          NPARAMS is INTEGER
310 *>     Specifies the number of parameters set in PARAMS.  If .LE. 0, the
311 *>     PARAMS array is never referenced and default values are used.
312 *> \endverbatim
313 *>
314 *> \param[in,out] PARAMS
315 *> \verbatim
316 *>          PARAMS is REAL array, dimension NPARAMS
317 *>     Specifies algorithm parameters.  If an entry is .LT. 0.0, then
318 *>     that entry will be filled with default value used for that
319 *>     parameter.  Only positions up to NPARAMS are accessed; defaults
320 *>     are used for higher-numbered parameters.
321 *>
322 *>       PARAMS(LA_LINRX_ITREF_I = 1) : Whether to perform iterative
323 *>            refinement or not.
324 *>         Default: 1.0
325 *>            = 0.0 : No refinement is performed, and no error bounds are
326 *>                    computed.
327 *>            = 1.0 : Use the double-precision refinement algorithm,
328 *>                    possibly with doubled-single computations if the
329 *>                    compilation environment does not support DOUBLE
330 *>                    PRECISION.
331 *>              (other values are reserved for future use)
332 *>
333 *>       PARAMS(LA_LINRX_ITHRESH_I = 2) : Maximum number of residual
334 *>            computations allowed for refinement.
335 *>         Default: 10
336 *>         Aggressive: Set to 100 to permit convergence using approximate
337 *>                     factorizations or factorizations other than LU. If
338 *>                     the factorization uses a technique other than
339 *>                     Gaussian elimination, the guarantees in
340 *>                     err_bnds_norm and err_bnds_comp may no longer be
341 *>                     trustworthy.
342 *>
343 *>       PARAMS(LA_LINRX_CWISE_I = 3) : Flag determining if the code
344 *>            will attempt to find a solution with small componentwise
345 *>            relative error in the double-precision algorithm.  Positive
346 *>            is true, 0.0 is false.
347 *>         Default: 1.0 (attempt componentwise convergence)
348 *> \endverbatim
349 *>
350 *> \param[out] WORK
351 *> \verbatim
352 *>          WORK is REAL array, dimension (4*N)
353 *> \endverbatim
354 *>
355 *> \param[out] IWORK
356 *> \verbatim
357 *>          IWORK is INTEGER array, dimension (N)
358 *> \endverbatim
359 *>
360 *> \param[out] INFO
361 *> \verbatim
362 *>          INFO is INTEGER
363 *>       = 0:  Successful exit. The solution to every right-hand side is
364 *>         guaranteed.
365 *>       < 0:  If INFO = -i, the i-th argument had an illegal value
366 *>       > 0 and <= N:  U(INFO,INFO) is exactly zero.  The factorization
367 *>         has been completed, but the factor U is exactly singular, so
368 *>         the solution and error bounds could not be computed. RCOND = 0
369 *>         is returned.
370 *>       = N+J: The solution corresponding to the Jth right-hand side is
371 *>         not guaranteed. The solutions corresponding to other right-
372 *>         hand sides K with K > J may not be guaranteed as well, but
373 *>         only the first such right-hand side is reported. If a small
374 *>         componentwise error is not requested (PARAMS(3) = 0.0) then
375 *>         the Jth right-hand side is the first with a normwise error
376 *>         bound that is not guaranteed (the smallest J such
377 *>         that ERR_BNDS_NORM(J,1) = 0.0). By default (PARAMS(3) = 1.0)
378 *>         the Jth right-hand side is the first with either a normwise or
379 *>         componentwise error bound that is not guaranteed (the smallest
380 *>         J such that either ERR_BNDS_NORM(J,1) = 0.0 or
381 *>         ERR_BNDS_COMP(J,1) = 0.0). See the definition of
382 *>         ERR_BNDS_NORM(:,1) and ERR_BNDS_COMP(:,1). To get information
383 *>         about all of the right-hand sides check ERR_BNDS_NORM or
384 *>         ERR_BNDS_COMP.
385 *> \endverbatim
386 *
387 *  Authors:
388 *  ========
389 *
390 *> \author Univ. of Tennessee
391 *> \author Univ. of California Berkeley
392 *> \author Univ. of Colorado Denver
393 *> \author NAG Ltd.
394 *
395 *> \date April 2012
396 *
397 *> \ingroup realSYcomputational
398 *
399 *  =====================================================================
400       SUBROUTINE SSYRFSX( UPLO, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV,
401      $                    S, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS,
402      $                    ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS,
403      $                    WORK, IWORK, INFO )
404 *
405 *  -- LAPACK computational routine (version 3.4.1) --
406 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
407 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
408 *     April 2012
409 *
410 *     .. Scalar Arguments ..
411       CHARACTER          UPLO, EQUED
412       INTEGER            INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
413      $                   N_ERR_BNDS
414       REAL               RCOND
415 *     ..
416 *     .. Array Arguments ..
417       INTEGER            IPIV( * ), IWORK( * )
418       REAL               A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
419      $                   X( LDX, * ), WORK( * )
420       REAL               S( * ), PARAMS( * ), BERR( * ),
421      $                   ERR_BNDS_NORM( NRHS, * ),
422      $                   ERR_BNDS_COMP( NRHS, * )
423 *     ..
424 *
425 *  ==================================================================
426 *
427 *     .. Parameters ..
428       REAL               ZERO, ONE
429       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
430       REAL               ITREF_DEFAULT, ITHRESH_DEFAULT,
431      $                   COMPONENTWISE_DEFAULT
432       REAL               RTHRESH_DEFAULT, DZTHRESH_DEFAULT
433       PARAMETER          ( ITREF_DEFAULT = 1.0 )
434       PARAMETER          ( ITHRESH_DEFAULT = 10.0 )
435       PARAMETER          ( COMPONENTWISE_DEFAULT = 1.0 )
436       PARAMETER          ( RTHRESH_DEFAULT = 0.5 )
437       PARAMETER          ( DZTHRESH_DEFAULT = 0.25 )
438       INTEGER            LA_LINRX_ITREF_I, LA_LINRX_ITHRESH_I,
439      $                   LA_LINRX_CWISE_I
440       PARAMETER          ( LA_LINRX_ITREF_I = 1,
441      $                   LA_LINRX_ITHRESH_I = 2 )
442       PARAMETER          ( LA_LINRX_CWISE_I = 3 )
443       INTEGER            LA_LINRX_TRUST_I, LA_LINRX_ERR_I,
444      $                   LA_LINRX_RCOND_I
445       PARAMETER          ( LA_LINRX_TRUST_I = 1, LA_LINRX_ERR_I = 2 )
446       PARAMETER          ( LA_LINRX_RCOND_I = 3 )
447 *     ..
448 *     .. Local Scalars ..
449       CHARACTER(1)       NORM
450       LOGICAL            RCEQU
451       INTEGER            J, PREC_TYPE, REF_TYPE, N_NORMS
452       REAL               ANORM, RCOND_TMP
453       REAL               ILLRCOND_THRESH, ERR_LBND, CWISE_WRONG
454       LOGICAL            IGNORE_CWISE
455       INTEGER            ITHRESH
456       REAL               RTHRESH, UNSTABLE_THRESH
457 *     ..
458 *     .. External Subroutines ..
459       EXTERNAL           XERBLA, SSYCON, SLA_SYRFSX_EXTENDED
460 *     ..
461 *     .. Intrinsic Functions ..
462       INTRINSIC          MAX, SQRT
463 *     ..
464 *     .. External Functions ..
465       EXTERNAL           LSAME, ILAPREC
466       EXTERNAL           SLAMCH, SLANSY, SLA_SYRCOND
467       REAL               SLAMCH, SLANSY, SLA_SYRCOND
468       LOGICAL            LSAME
469       INTEGER            ILAPREC
470 *     ..
471 *     .. Executable Statements ..
472 *
473 *     Check the input parameters.
474 *
475       INFO = 0
476       REF_TYPE = INT( ITREF_DEFAULT )
477       IF ( NPARAMS .GE. LA_LINRX_ITREF_I ) THEN
478          IF ( PARAMS( LA_LINRX_ITREF_I ) .LT. 0.0 ) THEN
479             PARAMS( LA_LINRX_ITREF_I ) = ITREF_DEFAULT
480          ELSE
481             REF_TYPE = PARAMS( LA_LINRX_ITREF_I )
482          END IF
483       END IF
484 *
485 *     Set default parameters.
486 *
487       ILLRCOND_THRESH = REAL( N )*SLAMCH( 'Epsilon' )
488       ITHRESH = INT( ITHRESH_DEFAULT )
489       RTHRESH = RTHRESH_DEFAULT
490       UNSTABLE_THRESH = DZTHRESH_DEFAULT
491       IGNORE_CWISE = COMPONENTWISE_DEFAULT .EQ. 0.0
492 *
493       IF ( NPARAMS.GE.LA_LINRX_ITHRESH_I ) THEN
494          IF ( PARAMS( LA_LINRX_ITHRESH_I ).LT.0.0 ) THEN
495             PARAMS( LA_LINRX_ITHRESH_I ) = ITHRESH
496          ELSE
497             ITHRESH = INT( PARAMS( LA_LINRX_ITHRESH_I ) )
498          END IF
499       END IF
500       IF ( NPARAMS.GE.LA_LINRX_CWISE_I ) THEN
501          IF ( PARAMS( LA_LINRX_CWISE_I ).LT.0.0 ) THEN
502             IF ( IGNORE_CWISE ) THEN
503                PARAMS( LA_LINRX_CWISE_I ) = 0.0
504             ELSE
505                PARAMS( LA_LINRX_CWISE_I ) = 1.0
506             END IF
507          ELSE
508             IGNORE_CWISE = PARAMS( LA_LINRX_CWISE_I ) .EQ. 0.0
509          END IF
510       END IF
511       IF ( REF_TYPE .EQ. 0 .OR. N_ERR_BNDS .EQ. 0 ) THEN
512          N_NORMS = 0
513       ELSE IF ( IGNORE_CWISE ) THEN
514          N_NORMS = 1
515       ELSE
516          N_NORMS = 2
517       END IF
518 *
519       RCEQU = LSAME( EQUED, 'Y' )
520 *
521 *     Test input parameters.
522 *
523       IF ( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
524         INFO = -1
525       ELSE IF( .NOT.RCEQU .AND. .NOT.LSAME( EQUED, 'N' ) ) THEN
526         INFO = -2
527       ELSE IF( N.LT.0 ) THEN
528         INFO = -3
529       ELSE IF( NRHS.LT.0 ) THEN
530         INFO = -4
531       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
532         INFO = -6
533       ELSE IF( LDAF.LT.MAX( 1, N ) ) THEN
534         INFO = -8
535       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
536         INFO = -12
537       ELSE IF( LDX.LT.MAX( 1, N ) ) THEN
538         INFO = -14
539       END IF
540       IF( INFO.NE.0 ) THEN
541         CALL XERBLA( 'SSYRFSX', -INFO )
542         RETURN
543       END IF
544 *
545 *     Quick return if possible.
546 *
547       IF( N.EQ.0 .OR. NRHS.EQ.0 ) THEN
548          RCOND = 1.0
549          DO J = 1, NRHS
550             BERR( J ) = 0.0
551             IF ( N_ERR_BNDS .GE. 1 ) THEN
552                ERR_BNDS_NORM( J, LA_LINRX_TRUST_I ) = 1.0
553                ERR_BNDS_COMP( J, LA_LINRX_TRUST_I ) = 1.0
554             END IF
555             IF ( N_ERR_BNDS .GE. 2 ) THEN
556                ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) = 0.0
557                ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) = 0.0
558             END IF
559             IF ( N_ERR_BNDS .GE. 3 ) THEN
560                ERR_BNDS_NORM( J, LA_LINRX_RCOND_I ) = 1.0
561                ERR_BNDS_COMP( J, LA_LINRX_RCOND_I ) = 1.0
562             END IF
563          END DO
564          RETURN
565       END IF
566 *
567 *     Default to failure.
568 *
569       RCOND = 0.0
570       DO J = 1, NRHS
571          BERR( J ) = 1.0
572          IF ( N_ERR_BNDS .GE. 1 ) THEN
573             ERR_BNDS_NORM( J, LA_LINRX_TRUST_I ) = 1.0
574             ERR_BNDS_COMP( J, LA_LINRX_TRUST_I ) = 1.0
575          END IF
576          IF ( N_ERR_BNDS .GE. 2 ) THEN
577             ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) = 1.0
578             ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) = 1.0
579          END IF
580          IF ( N_ERR_BNDS .GE. 3 ) THEN
581             ERR_BNDS_NORM( J, LA_LINRX_RCOND_I ) = 0.0
582             ERR_BNDS_COMP( J, LA_LINRX_RCOND_I ) = 0.0
583          END IF
584       END DO
585 *
586 *     Compute the norm of A and the reciprocal of the condition
587 *     number of A.
588 *
589       NORM = 'I'
590       ANORM = SLANSY( NORM, UPLO, N, A, LDA, WORK )
591       CALL SSYCON( UPLO, N, AF, LDAF, IPIV, ANORM, RCOND, WORK,
592      $     IWORK, INFO )
593 *
594 *     Perform refinement on each right-hand side
595 *
596       IF ( REF_TYPE .NE. 0 ) THEN
597
598          PREC_TYPE = ILAPREC( 'D' )
599
600          CALL SLA_SYRFSX_EXTENDED( PREC_TYPE, UPLO,  N,
601      $        NRHS, A, LDA, AF, LDAF, IPIV, RCEQU, S, B,
602      $        LDB, X, LDX, BERR, N_NORMS, ERR_BNDS_NORM, ERR_BNDS_COMP,
603      $        WORK( N+1 ), WORK( 1 ), WORK( 2*N+1 ), WORK( 1 ), RCOND,
604      $        ITHRESH, RTHRESH, UNSTABLE_THRESH, IGNORE_CWISE,
605      $        INFO )
606       END IF
607
608       ERR_LBND = MAX( 10.0, SQRT( REAL( N ) ) )*SLAMCH( 'Epsilon' )
609       IF (N_ERR_BNDS .GE. 1 .AND. N_NORMS .GE. 1) THEN
610 *
611 *     Compute scaled normwise condition number cond(A*C).
612 *
613          IF ( RCEQU ) THEN
614             RCOND_TMP = SLA_SYRCOND( UPLO, N, A, LDA, AF, LDAF, IPIV,
615      $           -1, S, INFO, WORK, IWORK )
616          ELSE
617             RCOND_TMP = SLA_SYRCOND( UPLO, N, A, LDA, AF, LDAF, IPIV,
618      $           0, S, INFO, WORK, IWORK )
619          END IF
620          DO J = 1, NRHS
621 *
622 *     Cap the error at 1.0.
623 *
624             IF (N_ERR_BNDS .GE. LA_LINRX_ERR_I
625      $           .AND. ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) .GT. 1.0)
626      $           ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) = 1.0
627 *
628 *     Threshold the error (see LAWN).
629 *
630             IF ( RCOND_TMP .LT. ILLRCOND_THRESH ) THEN
631                ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) = 1.0
632                ERR_BNDS_NORM( J, LA_LINRX_TRUST_I ) = 0.0
633                IF ( INFO .LE. N ) INFO = N + J
634             ELSE IF (ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) .LT. ERR_LBND)
635      $              THEN
636                ERR_BNDS_NORM( J, LA_LINRX_ERR_I ) = ERR_LBND
637                ERR_BNDS_NORM( J, LA_LINRX_TRUST_I ) = 1.0
638             END IF
639 *
640 *     Save the condition number.
641 *
642             IF (N_ERR_BNDS .GE. LA_LINRX_RCOND_I) THEN
643                ERR_BNDS_NORM( J, LA_LINRX_RCOND_I ) = RCOND_TMP
644             END IF
645          END DO
646       END IF
647
648       IF ( N_ERR_BNDS .GE. 1 .AND. N_NORMS .GE. 2 ) THEN
649 *
650 *     Compute componentwise condition number cond(A*diag(Y(:,J))) for
651 *     each right-hand side using the current solution as an estimate of
652 *     the true solution.  If the componentwise error estimate is too
653 *     large, then the solution is a lousy estimate of truth and the
654 *     estimated RCOND may be too optimistic.  To avoid misleading users,
655 *     the inverse condition number is set to 0.0 when the estimated
656 *     cwise error is at least CWISE_WRONG.
657 *
658          CWISE_WRONG = SQRT( SLAMCH( 'Epsilon' ) )
659          DO J = 1, NRHS
660             IF ( ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) .LT. CWISE_WRONG )
661      $     THEN
662                RCOND_TMP = SLA_SYRCOND( UPLO, N, A, LDA, AF, LDAF, IPIV,
663      $              1, X(1,J), INFO, WORK, IWORK )
664             ELSE
665                RCOND_TMP = 0.0
666             END IF
667 *
668 *     Cap the error at 1.0.
669 *
670             IF ( N_ERR_BNDS .GE. LA_LINRX_ERR_I
671      $           .AND. ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) .GT. 1.0 )
672      $           ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) = 1.0
673 *
674 *     Threshold the error (see LAWN).
675 *
676             IF ( RCOND_TMP .LT. ILLRCOND_THRESH ) THEN
677                ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) = 1.0
678                ERR_BNDS_COMP( J, LA_LINRX_TRUST_I ) = 0.0
679                IF ( .NOT. IGNORE_CWISE
680      $              .AND. INFO.LT.N + J ) INFO = N + J
681             ELSE IF ( ERR_BNDS_COMP( J, LA_LINRX_ERR_I )
682      $              .LT. ERR_LBND ) THEN
683                ERR_BNDS_COMP( J, LA_LINRX_ERR_I ) = ERR_LBND
684                ERR_BNDS_COMP( J, LA_LINRX_TRUST_I ) = 1.0
685             END IF
686 *
687 *     Save the condition number.
688 *
689             IF ( N_ERR_BNDS .GE. LA_LINRX_RCOND_I ) THEN
690                ERR_BNDS_COMP( J, LA_LINRX_RCOND_I ) = RCOND_TMP
691             END IF
692
693          END DO
694       END IF
695 *
696       RETURN
697 *
698 *     End of SSYRFSX
699 *
700       END