169 SUBROUTINE spprfs( UPLO, N, NRHS, AP, AFP, B, LDB, X, LDX, FERR,
170 $ BERR, WORK, IWORK, INFO )
178 INTEGER INFO, LDB, LDX, N, NRHS
182 REAL AFP( * ), AP( * ), B( LDB, * ), BERR( * ),
183 $ ferr( * ), work( * ), x( ldx, * )
190 parameter( itmax = 5 )
192 parameter( zero = 0.0e+0 )
194 parameter( one = 1.0e+0 )
196 parameter( two = 2.0e+0 )
198 parameter( three = 3.0e+0 )
202 INTEGER COUNT, I, IK, J, K, KASE, KK, NZ
203 REAL EPS, LSTRES, S, SAFE1, SAFE2, SAFMIN, XK
217 EXTERNAL lsame, slamch
224 upper = lsame( uplo,
'U' )
225 IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
227 ELSE IF( n.LT.0 )
THEN
229 ELSE IF( nrhs.LT.0 )
THEN
231 ELSE IF( ldb.LT.max( 1, n ) )
THEN
233 ELSE IF( ldx.LT.max( 1, n ) )
THEN
237 CALL xerbla(
'SPPRFS', -info )
243 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
254 eps = slamch(
'Epsilon' )
255 safmin = slamch(
'Safe minimum' )
271 CALL scopy( n, b( 1, j ), 1, work( n+1 ), 1 )
272 CALL sspmv( uplo, n, -one, ap, x( 1, j ), 1, one, work( n+1 ),
285 work( i ) = abs( b( i, j ) )
294 xk = abs( x( k, j ) )
297 work( i ) = work( i ) + abs( ap( ik ) )*xk
298 s = s + abs( ap( ik ) )*abs( x( i, j ) )
301 work( k ) = work( k ) + abs( ap( kk+k-1 ) )*xk + s
307 xk = abs( x( k, j ) )
308 work( k ) = work( k ) + abs( ap( kk ) )*xk
311 work( i ) = work( i ) + abs( ap( ik ) )*xk
312 s = s + abs( ap( ik ) )*abs( x( i, j ) )
315 work( k ) = work( k ) + s
321 IF( work( i ).GT.safe2 )
THEN
322 s = max( s, abs( work( n+i ) ) / work( i ) )
324 s = max( s, ( abs( work( n+i ) )+safe1 ) /
325 $ ( work( i )+safe1 ) )
336 IF( berr( j ).GT.eps .AND. two*berr( j ).LE.lstres .AND.
337 $ count.LE.itmax )
THEN
341 CALL spptrs( uplo, n, 1, afp, work( n+1 ), n, info )
342 CALL saxpy( n, one, work( n+1 ), 1, x( 1, j ), 1 )
371 IF( work( i ).GT.safe2 )
THEN
372 work( i ) = abs( work( n+i ) ) + nz*eps*work( i )
374 work( i ) = abs( work( n+i ) ) + nz*eps*work( i ) + safe1
380 CALL slacn2( n, work( 2*n+1 ), work( n+1 ), iwork, ferr( j ),
387 CALL spptrs( uplo, n, 1, afp, work( n+1 ), n, info )
389 work( n+i ) = work( i )*work( n+i )
391 ELSE IF( kase.EQ.2 )
THEN
396 work( n+i ) = work( i )*work( n+i )
398 CALL spptrs( uplo, n, 1, afp, work( n+1 ), n, info )
407 lstres = max( lstres, abs( x( i, j ) ) )
410 $ ferr( j ) = ferr( j ) / lstres
subroutine xerbla(srname, info)
subroutine saxpy(n, sa, sx, incx, sy, incy)
SAXPY
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine sspmv(uplo, n, alpha, ap, x, incx, beta, y, incy)
SSPMV
subroutine slacn2(n, v, x, isgn, est, kase, isave)
SLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine spprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPPRFS
subroutine spptrs(uplo, n, nrhs, ap, b, ldb, info)
SPPTRS