001:       SUBROUTINE SGESVX( FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV,
002:      $                   EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR,
003:      $                   WORK, IWORK, INFO )
004: *
005: *  -- LAPACK driver routine (version 3.2) --
006: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
007: *     November 2006
008: *
009: *     .. Scalar Arguments ..
010:       CHARACTER          EQUED, FACT, TRANS
011:       INTEGER            INFO, LDA, LDAF, LDB, LDX, N, NRHS
012:       REAL               RCOND
013: *     ..
014: *     .. Array Arguments ..
015:       INTEGER            IPIV( * ), IWORK( * )
016:       REAL               A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
017:      $                   BERR( * ), C( * ), FERR( * ), R( * ),
018:      $                   WORK( * ), X( LDX, * )
019: *     ..
020: *
021: *  Purpose
022: *  =======
023: *
024: *  SGESVX uses the LU factorization to compute the solution to a real
025: *  system of linear equations
026: *     A * X = B,
027: *  where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
028: *
029: *  Error bounds on the solution and a condition estimate are also
030: *  provided.
031: *
032: *  Description
033: *  ===========
034: *
035: *  The following steps are performed:
036: *
037: *  1. If FACT = 'E', real scaling factors are computed to equilibrate
038: *     the system:
039: *        TRANS = 'N':  diag(R)*A*diag(C)     *inv(diag(C))*X = diag(R)*B
040: *        TRANS = 'T': (diag(R)*A*diag(C))**T *inv(diag(R))*X = diag(C)*B
041: *        TRANS = 'C': (diag(R)*A*diag(C))**H *inv(diag(R))*X = diag(C)*B
042: *     Whether or not the system will be equilibrated depends on the
043: *     scaling of the matrix A, but if equilibration is used, A is
044: *     overwritten by diag(R)*A*diag(C) and B by diag(R)*B (if TRANS='N')
045: *     or diag(C)*B (if TRANS = 'T' or 'C').
046: *
047: *  2. If FACT = 'N' or 'E', the LU decomposition is used to factor the
048: *     matrix A (after equilibration if FACT = 'E') as
049: *        A = P * L * U,
050: *     where P is a permutation matrix, L is a unit lower triangular
051: *     matrix, and U is upper triangular.
052: *
053: *  3. If some U(i,i)=0, so that U is exactly singular, then the routine
054: *     returns with INFO = i. Otherwise, the factored form of A is used
055: *     to estimate the condition number of the matrix A.  If the
056: *     reciprocal of the condition number is less than machine precision,
057: *     INFO = N+1 is returned as a warning, but the routine still goes on
058: *     to solve for X and compute error bounds as described below.
059: *
060: *  4. The system of equations is solved for X using the factored form
061: *     of A.
062: *
063: *  5. Iterative refinement is applied to improve the computed solution
064: *     matrix and calculate error bounds and backward error estimates
065: *     for it.
066: *
067: *  6. If equilibration was used, the matrix X is premultiplied by
068: *     diag(C) (if TRANS = 'N') or diag(R) (if TRANS = 'T' or 'C') so
069: *     that it solves the original system before equilibration.
070: *
071: *  Arguments
072: *  =========
073: *
074: *  FACT    (input) CHARACTER*1
075: *          Specifies whether or not the factored form of the matrix A is
076: *          supplied on entry, and if not, whether the matrix A should be
077: *          equilibrated before it is factored.
078: *          = 'F':  On entry, AF and IPIV contain the factored form of A.
079: *                  If EQUED is not 'N', the matrix A has been
080: *                  equilibrated with scaling factors given by R and C.
081: *                  A, AF, and IPIV are not modified.
082: *          = 'N':  The matrix A will be copied to AF and factored.
083: *          = 'E':  The matrix A will be equilibrated if necessary, then
084: *                  copied to AF and factored.
085: *
086: *  TRANS   (input) CHARACTER*1
087: *          Specifies the form of the system of equations:
088: *          = 'N':  A * X = B     (No transpose)
089: *          = 'T':  A**T * X = B  (Transpose)
090: *          = 'C':  A**H * X = B  (Transpose)
091: *
092: *  N       (input) INTEGER
093: *          The number of linear equations, i.e., the order of the
094: *          matrix A.  N >= 0.
095: *
096: *  NRHS    (input) INTEGER
097: *          The number of right hand sides, i.e., the number of columns
098: *          of the matrices B and X.  NRHS >= 0.
099: *
100: *  A       (input/output) REAL array, dimension (LDA,N)
101: *          On entry, the N-by-N matrix A.  If FACT = 'F' and EQUED is
102: *          not 'N', then A must have been equilibrated by the scaling
103: *          factors in R and/or C.  A is not modified if FACT = 'F' or
104: *          'N', or if FACT = 'E' and EQUED = 'N' on exit.
105: *
106: *          On exit, if EQUED .ne. 'N', A is scaled as follows:
107: *          EQUED = 'R':  A := diag(R) * A
108: *          EQUED = 'C':  A := A * diag(C)
109: *          EQUED = 'B':  A := diag(R) * A * diag(C).
110: *
111: *  LDA     (input) INTEGER
112: *          The leading dimension of the array A.  LDA >= max(1,N).
113: *
114: *  AF      (input or output) REAL array, dimension (LDAF,N)
115: *          If FACT = 'F', then AF is an input argument and on entry
116: *          contains the factors L and U from the factorization
117: *          A = P*L*U as computed by SGETRF.  If EQUED .ne. 'N', then
118: *          AF is the factored form of the equilibrated matrix A.
119: *
120: *          If FACT = 'N', then AF is an output argument and on exit
121: *          returns the factors L and U from the factorization A = P*L*U
122: *          of the original matrix A.
123: *
124: *          If FACT = 'E', then AF is an output argument and on exit
125: *          returns the factors L and U from the factorization A = P*L*U
126: *          of the equilibrated matrix A (see the description of A for
127: *          the form of the equilibrated matrix).
128: *
129: *  LDAF    (input) INTEGER
130: *          The leading dimension of the array AF.  LDAF >= max(1,N).
131: *
132: *  IPIV    (input or output) INTEGER array, dimension (N)
133: *          If FACT = 'F', then IPIV is an input argument and on entry
134: *          contains the pivot indices from the factorization A = P*L*U
135: *          as computed by SGETRF; row i of the matrix was interchanged
136: *          with row IPIV(i).
137: *
138: *          If FACT = 'N', then IPIV is an output argument and on exit
139: *          contains the pivot indices from the factorization A = P*L*U
140: *          of the original matrix A.
141: *
142: *          If FACT = 'E', then IPIV is an output argument and on exit
143: *          contains the pivot indices from the factorization A = P*L*U
144: *          of the equilibrated matrix A.
145: *
146: *  EQUED   (input or output) CHARACTER*1
147: *          Specifies the form of equilibration that was done.
148: *          = 'N':  No equilibration (always true if FACT = 'N').
149: *          = 'R':  Row equilibration, i.e., A has been premultiplied by
150: *                  diag(R).
151: *          = 'C':  Column equilibration, i.e., A has been postmultiplied
152: *                  by diag(C).
153: *          = 'B':  Both row and column equilibration, i.e., A has been
154: *                  replaced by diag(R) * A * diag(C).
155: *          EQUED is an input argument if FACT = 'F'; otherwise, it is an
156: *          output argument.
157: *
158: *  R       (input or output) REAL array, dimension (N)
159: *          The row scale factors for A.  If EQUED = 'R' or 'B', A is
160: *          multiplied on the left by diag(R); if EQUED = 'N' or 'C', R
161: *          is not accessed.  R is an input argument if FACT = 'F';
162: *          otherwise, R is an output argument.  If FACT = 'F' and
163: *          EQUED = 'R' or 'B', each element of R must be positive.
164: *
165: *  C       (input or output) REAL array, dimension (N)
166: *          The column scale factors for A.  If EQUED = 'C' or 'B', A is
167: *          multiplied on the right by diag(C); if EQUED = 'N' or 'R', C
168: *          is not accessed.  C is an input argument if FACT = 'F';
169: *          otherwise, C is an output argument.  If FACT = 'F' and
170: *          EQUED = 'C' or 'B', each element of C must be positive.
171: *
172: *  B       (input/output) REAL array, dimension (LDB,NRHS)
173: *          On entry, the N-by-NRHS right hand side matrix B.
174: *          On exit,
175: *          if EQUED = 'N', B is not modified;
176: *          if TRANS = 'N' and EQUED = 'R' or 'B', B is overwritten by
177: *          diag(R)*B;
178: *          if TRANS = 'T' or 'C' and EQUED = 'C' or 'B', B is
179: *          overwritten by diag(C)*B.
180: *
181: *  LDB     (input) INTEGER
182: *          The leading dimension of the array B.  LDB >= max(1,N).
183: *
184: *  X       (output) REAL array, dimension (LDX,NRHS)
185: *          If INFO = 0 or INFO = N+1, the N-by-NRHS solution matrix X
186: *          to the original system of equations.  Note that A and B are
187: *          modified on exit if EQUED .ne. 'N', and the solution to the
188: *          equilibrated system is inv(diag(C))*X if TRANS = 'N' and
189: *          EQUED = 'C' or 'B', or inv(diag(R))*X if TRANS = 'T' or 'C'
190: *          and EQUED = 'R' or 'B'.
191: *
192: *  LDX     (input) INTEGER
193: *          The leading dimension of the array X.  LDX >= max(1,N).
194: *
195: *  RCOND   (output) REAL
196: *          The estimate of the reciprocal condition number of the matrix
197: *          A after equilibration (if done).  If RCOND is less than the
198: *          machine precision (in particular, if RCOND = 0), the matrix
199: *          is singular to working precision.  This condition is
200: *          indicated by a return code of INFO > 0.
201: *
202: *  FERR    (output) REAL array, dimension (NRHS)
203: *          The estimated forward error bound for each solution vector
204: *          X(j) (the j-th column of the solution matrix X).
205: *          If XTRUE is the true solution corresponding to X(j), FERR(j)
206: *          is an estimated upper bound for the magnitude of the largest
207: *          element in (X(j) - XTRUE) divided by the magnitude of the
208: *          largest element in X(j).  The estimate is as reliable as
209: *          the estimate for RCOND, and is almost always a slight
210: *          overestimate of the true error.
211: *
212: *  BERR    (output) REAL array, dimension (NRHS)
213: *          The componentwise relative backward error of each solution
214: *          vector X(j) (i.e., the smallest relative change in
215: *          any element of A or B that makes X(j) an exact solution).
216: *
217: *  WORK    (workspace/output) REAL array, dimension (4*N)
218: *          On exit, WORK(1) contains the reciprocal pivot growth
219: *          factor norm(A)/norm(U). The "max absolute element" norm is
220: *          used. If WORK(1) is much less than 1, then the stability
221: *          of the LU factorization of the (equilibrated) matrix A
222: *          could be poor. This also means that the solution X, condition
223: *          estimator RCOND, and forward error bound FERR could be
224: *          unreliable. If factorization fails with 0<INFO<=N, then
225: *          WORK(1) contains the reciprocal pivot growth factor for the
226: *          leading INFO columns of A.
227: *
228: *  IWORK   (workspace) INTEGER array, dimension (N)
229: *
230: *  INFO    (output) INTEGER
231: *          = 0:  successful exit
232: *          < 0:  if INFO = -i, the i-th argument had an illegal value
233: *          > 0:  if INFO = i, and i is
234: *                <= N:  U(i,i) is exactly zero.  The factorization has
235: *                       been completed, but the factor U is exactly
236: *                       singular, so the solution and error bounds
237: *                       could not be computed. RCOND = 0 is returned.
238: *                = N+1: U is nonsingular, but RCOND is less than machine
239: *                       precision, meaning that the matrix is singular
240: *                       to working precision.  Nevertheless, the
241: *                       solution and error bounds are computed because
242: *                       there are a number of situations where the
243: *                       computed solution can be more accurate than the
244: *                       value of RCOND would suggest.
245: *
246: *  =====================================================================
247: *
248: *     .. Parameters ..
249:       REAL               ZERO, ONE
250:       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
251: *     ..
252: *     .. Local Scalars ..
253:       LOGICAL            COLEQU, EQUIL, NOFACT, NOTRAN, ROWEQU
254:       CHARACTER          NORM
255:       INTEGER            I, INFEQU, J
256:       REAL               AMAX, ANORM, BIGNUM, COLCND, RCMAX, RCMIN,
257:      $                   ROWCND, RPVGRW, SMLNUM
258: *     ..
259: *     .. External Functions ..
260:       LOGICAL            LSAME
261:       REAL               SLAMCH, SLANGE, SLANTR
262:       EXTERNAL           LSAME, SLAMCH, SLANGE, SLANTR
263: *     ..
264: *     .. External Subroutines ..
265:       EXTERNAL           SGECON, SGEEQU, SGERFS, SGETRF, SGETRS, SLACPY,
266:      $                   SLAQGE, XERBLA
267: *     ..
268: *     .. Intrinsic Functions ..
269:       INTRINSIC          MAX, MIN
270: *     ..
271: *     .. Executable Statements ..
272: *
273:       INFO = 0
274:       NOFACT = LSAME( FACT, 'N' )
275:       EQUIL = LSAME( FACT, 'E' )
276:       NOTRAN = LSAME( TRANS, 'N' )
277:       IF( NOFACT .OR. EQUIL ) THEN
278:          EQUED = 'N'
279:          ROWEQU = .FALSE.
280:          COLEQU = .FALSE.
281:       ELSE
282:          ROWEQU = LSAME( EQUED, 'R' ) .OR. LSAME( EQUED, 'B' )
283:          COLEQU = LSAME( EQUED, 'C' ) .OR. LSAME( EQUED, 'B' )
284:          SMLNUM = SLAMCH( 'Safe minimum' )
285:          BIGNUM = ONE / SMLNUM
286:       END IF
287: *
288: *     Test the input parameters.
289: *
290:       IF( .NOT.NOFACT .AND. .NOT.EQUIL .AND. .NOT.LSAME( FACT, 'F' ) )
291:      $     THEN
292:          INFO = -1
293:       ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) .AND. .NOT.
294:      $         LSAME( TRANS, 'C' ) ) THEN
295:          INFO = -2
296:       ELSE IF( N.LT.0 ) THEN
297:          INFO = -3
298:       ELSE IF( NRHS.LT.0 ) THEN
299:          INFO = -4
300:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
301:          INFO = -6
302:       ELSE IF( LDAF.LT.MAX( 1, N ) ) THEN
303:          INFO = -8
304:       ELSE IF( LSAME( FACT, 'F' ) .AND. .NOT.
305:      $         ( ROWEQU .OR. COLEQU .OR. LSAME( EQUED, 'N' ) ) ) THEN
306:          INFO = -10
307:       ELSE
308:          IF( ROWEQU ) THEN
309:             RCMIN = BIGNUM
310:             RCMAX = ZERO
311:             DO 10 J = 1, N
312:                RCMIN = MIN( RCMIN, R( J ) )
313:                RCMAX = MAX( RCMAX, R( J ) )
314:    10       CONTINUE
315:             IF( RCMIN.LE.ZERO ) THEN
316:                INFO = -11
317:             ELSE IF( N.GT.0 ) THEN
318:                ROWCND = MAX( RCMIN, SMLNUM ) / MIN( RCMAX, BIGNUM )
319:             ELSE
320:                ROWCND = ONE
321:             END IF
322:          END IF
323:          IF( COLEQU .AND. INFO.EQ.0 ) THEN
324:             RCMIN = BIGNUM
325:             RCMAX = ZERO
326:             DO 20 J = 1, N
327:                RCMIN = MIN( RCMIN, C( J ) )
328:                RCMAX = MAX( RCMAX, C( J ) )
329:    20       CONTINUE
330:             IF( RCMIN.LE.ZERO ) THEN
331:                INFO = -12
332:             ELSE IF( N.GT.0 ) THEN
333:                COLCND = MAX( RCMIN, SMLNUM ) / MIN( RCMAX, BIGNUM )
334:             ELSE
335:                COLCND = ONE
336:             END IF
337:          END IF
338:          IF( INFO.EQ.0 ) THEN
339:             IF( LDB.LT.MAX( 1, N ) ) THEN
340:                INFO = -14
341:             ELSE IF( LDX.LT.MAX( 1, N ) ) THEN
342:                INFO = -16
343:             END IF
344:          END IF
345:       END IF
346: *
347:       IF( INFO.NE.0 ) THEN
348:          CALL XERBLA( 'SGESVX', -INFO )
349:          RETURN
350:       END IF
351: *
352:       IF( EQUIL ) THEN
353: *
354: *        Compute row and column scalings to equilibrate the matrix A.
355: *
356:          CALL SGEEQU( N, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFEQU )
357:          IF( INFEQU.EQ.0 ) THEN
358: *
359: *           Equilibrate the matrix.
360: *
361:             CALL SLAQGE( N, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
362:      $                   EQUED )
363:             ROWEQU = LSAME( EQUED, 'R' ) .OR. LSAME( EQUED, 'B' )
364:             COLEQU = LSAME( EQUED, 'C' ) .OR. LSAME( EQUED, 'B' )
365:          END IF
366:       END IF
367: *
368: *     Scale the right hand side.
369: *
370:       IF( NOTRAN ) THEN
371:          IF( ROWEQU ) THEN
372:             DO 40 J = 1, NRHS
373:                DO 30 I = 1, N
374:                   B( I, J ) = R( I )*B( I, J )
375:    30          CONTINUE
376:    40       CONTINUE
377:          END IF
378:       ELSE IF( COLEQU ) THEN
379:          DO 60 J = 1, NRHS
380:             DO 50 I = 1, N
381:                B( I, J ) = C( I )*B( I, J )
382:    50       CONTINUE
383:    60    CONTINUE
384:       END IF
385: *
386:       IF( NOFACT .OR. EQUIL ) THEN
387: *
388: *        Compute the LU factorization of A.
389: *
390:          CALL SLACPY( 'Full', N, N, A, LDA, AF, LDAF )
391:          CALL SGETRF( N, N, AF, LDAF, IPIV, INFO )
392: *
393: *        Return if INFO is non-zero.
394: *
395:          IF( INFO.GT.0 ) THEN
396: *
397: *           Compute the reciprocal pivot growth factor of the
398: *           leading rank-deficient INFO columns of A.
399: *
400:             RPVGRW = SLANTR( 'M', 'U', 'N', INFO, INFO, AF, LDAF,
401:      $               WORK )
402:             IF( RPVGRW.EQ.ZERO ) THEN
403:                RPVGRW = ONE
404:             ELSE
405:                RPVGRW = SLANGE( 'M', N, INFO, A, LDA, WORK ) / RPVGRW
406:             END IF
407:             WORK( 1 ) = RPVGRW
408:             RCOND = ZERO
409:             RETURN
410:          END IF
411:       END IF
412: *
413: *     Compute the norm of the matrix A and the
414: *     reciprocal pivot growth factor RPVGRW.
415: *
416:       IF( NOTRAN ) THEN
417:          NORM = '1'
418:       ELSE
419:          NORM = 'I'
420:       END IF
421:       ANORM = SLANGE( NORM, N, N, A, LDA, WORK )
422:       RPVGRW = SLANTR( 'M', 'U', 'N', N, N, AF, LDAF, WORK )
423:       IF( RPVGRW.EQ.ZERO ) THEN
424:          RPVGRW = ONE
425:       ELSE
426:          RPVGRW = SLANGE( 'M', N, N, A, LDA, WORK ) / RPVGRW
427:       END IF
428: *
429: *     Compute the reciprocal of the condition number of A.
430: *
431:       CALL SGECON( NORM, N, AF, LDAF, ANORM, RCOND, WORK, IWORK, INFO )
432: *
433: *     Compute the solution matrix X.
434: *
435:       CALL SLACPY( 'Full', N, NRHS, B, LDB, X, LDX )
436:       CALL SGETRS( TRANS, N, NRHS, AF, LDAF, IPIV, X, LDX, INFO )
437: *
438: *     Use iterative refinement to improve the computed solution and
439: *     compute error bounds and backward error estimates for it.
440: *
441:       CALL SGERFS( TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X,
442:      $             LDX, FERR, BERR, WORK, IWORK, INFO )
443: *
444: *     Transform the solution matrix X to a solution of the original
445: *     system.
446: *
447:       IF( NOTRAN ) THEN
448:          IF( COLEQU ) THEN
449:             DO 80 J = 1, NRHS
450:                DO 70 I = 1, N
451:                   X( I, J ) = C( I )*X( I, J )
452:    70          CONTINUE
453:    80       CONTINUE
454:             DO 90 J = 1, NRHS
455:                FERR( J ) = FERR( J ) / COLCND
456:    90       CONTINUE
457:          END IF
458:       ELSE IF( ROWEQU ) THEN
459:          DO 110 J = 1, NRHS
460:             DO 100 I = 1, N
461:                X( I, J ) = R( I )*X( I, J )
462:   100       CONTINUE
463:   110    CONTINUE
464:          DO 120 J = 1, NRHS
465:             FERR( J ) = FERR( J ) / ROWCND
466:   120    CONTINUE
467:       END IF
468: *
469: *     Set INFO = N+1 if the matrix is singular to working precision.
470: *
471:       IF( RCOND.LT.SLAMCH( 'Epsilon' ) )
472:      $   INFO = N + 1
473: *
474:       WORK( 1 ) = RPVGRW
475:       RETURN
476: *
477: *     End of SGESVX
478: *
479:       END
480: