137 SUBROUTINE sdrvgt( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, AF,
138 $ B, X, XACT, WORK, RWORK, IWORK, NOUT )
146 INTEGER NN, NOUT, NRHS
151 INTEGER IWORK( * ), NVAL( * )
152 REAL A( * ), AF( * ), B( * ), RWORK( * ), WORK( * ),
160 parameter( one = 1.0e+0, zero = 0.0e+0 )
162 parameter( ntypes = 12 )
164 parameter( ntests = 6 )
167 LOGICAL TRFCON, ZEROT
168 CHARACTER DIST, FACT, TRANS, TYPE
170 INTEGER I, IFACT, IMAT, IN, INFO, ITRAN, IX, IZERO, J,
171 $ k, k1, kl, koff, ku, lda, m, mode, n, nerrs,
172 $ nfail, nimat, nrun, nt
173 REAL AINVNM, ANORM, ANORMI, ANORMO, COND, RCOND,
174 $ rcondc, rcondi, rcondo
177 CHARACTER TRANSS( 3 )
178 INTEGER ISEED( 4 ), ISEEDY( 4 )
179 REAL RESULT( NTESTS ), Z( 3 )
182 REAL SASUM, SGET06, SLANGT
183 EXTERNAL sasum, sget06, slangt
200 COMMON / infoc / infot, nunit, ok, lerr
201 COMMON / srnamc / srnamt
204 DATA iseedy / 0, 0, 0, 1 / , transs /
'N',
'T',
209 path( 1: 1 ) =
'Single precision'
215 iseed( i ) = iseedy( i )
221 $
CALL serrvx( path, nout )
235 DO 130 imat = 1, nimat
239 IF( .NOT.dotype( imat ) )
244 CALL slatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
247 zerot = imat.GE.8 .AND. imat.LE.10
252 koff = max( 2-ku, 3-max( 1, n ) )
254 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode, cond,
255 $ anorm, kl, ku,
'Z', af( koff ), 3, work,
261 CALL alaerh( path,
'SLATMS', info, 0,
' ', n, n, kl,
262 $ ku, -1, imat, nfail, nerrs, nout )
268 CALL scopy( n-1, af( 4 ), 3, a, 1 )
269 CALL scopy( n-1, af( 3 ), 3, a( n+m+1 ), 1 )
271 CALL scopy( n, af( 2 ), 3, a( m+1 ), 1 )
277 IF( .NOT.zerot .OR. .NOT.dotype( 7 ) )
THEN
281 CALL slarnv( 2, iseed, n+2*m, a )
283 $
CALL sscal( n+2*m, anorm, a, 1 )
284 ELSE IF( izero.GT.0 )
THEN
289 IF( izero.EQ.1 )
THEN
293 ELSE IF( izero.EQ.n )
THEN
297 a( 2*n-2+izero ) = z( 1 )
298 a( n-1+izero ) = z( 2 )
305 IF( .NOT.zerot )
THEN
307 ELSE IF( imat.EQ.8 )
THEN
315 ELSE IF( imat.EQ.9 )
THEN
323 DO 20 i = izero, n - 1
334 IF( ifact.EQ.1 )
THEN
349 ELSE IF( ifact.EQ.1 )
THEN
350 CALL scopy( n+2*m, a, 1, af, 1 )
354 anormo = slangt(
'1', n, a, a( m+1 ), a( n+m+1 ) )
355 anormi = slangt(
'I', n, a, a( m+1 ), a( n+m+1 ) )
359 CALL sgttrf( n, af, af( m+1 ), af( n+m+1 ),
360 $ af( n+2*m+1 ), iwork, info )
371 CALL sgttrs(
'No transpose', n, 1, af, af( m+1 ),
372 $ af( n+m+1 ), af( n+2*m+1 ), iwork, x,
374 ainvnm = max( ainvnm, sasum( n, x, 1 ) )
379 IF( anormo.LE.zero .OR. ainvnm.LE.zero )
THEN
382 rcondo = ( one / anormo ) / ainvnm
394 CALL sgttrs(
'Transpose', n, 1, af, af( m+1 ),
395 $ af( n+m+1 ), af( n+2*m+1 ), iwork, x,
397 ainvnm = max( ainvnm, sasum( n, x, 1 ) )
402 IF( anormi.LE.zero .OR. ainvnm.LE.zero )
THEN
405 rcondi = ( one / anormi ) / ainvnm
410 trans = transs( itran )
411 IF( itran.EQ.1 )
THEN
421 CALL slarnv( 2, iseed, n, xact( ix ) )
427 CALL slagtm( trans, n, nrhs, one, a, a( m+1 ),
428 $ a( n+m+1 ), xact, lda, zero, b, lda )
430 IF( ifact.EQ.2 .AND. itran.EQ.1 )
THEN
437 CALL scopy( n+2*m, a, 1, af, 1 )
438 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
441 CALL sgtsv( n, nrhs, af, af( m+1 ), af( n+m+1 ), x,
447 $
CALL alaerh( path,
'SGTSV ', info, izero,
' ',
448 $ n, n, 1, 1, nrhs, imat, nfail,
451 IF( izero.EQ.0 )
THEN
455 CALL slacpy(
'Full', n, nrhs, b, lda, work,
457 CALL sgtt02( trans, n, nrhs, a, a( m+1 ),
458 $ a( n+m+1 ), x, lda, work, lda,
463 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
472 IF( result( k ).GE.thresh )
THEN
473 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
474 $
CALL aladhd( nout, path )
475 WRITE( nout, fmt = 9999 )
'SGTSV ', n, imat,
485 IF( ifact.GT.1 )
THEN
493 CALL slaset(
'Full', n, nrhs, zero, zero, x, lda )
499 CALL sgtsvx( fact, trans, n, nrhs, a, a( m+1 ),
500 $ a( n+m+1 ), af, af( m+1 ), af( n+m+1 ),
501 $ af( n+2*m+1 ), iwork, b, lda, x, lda,
502 $ rcond, rwork, rwork( nrhs+1 ), work,
503 $ iwork( n+1 ), info )
508 $
CALL alaerh( path,
'SGTSVX', info, izero,
509 $ fact // trans, n, n, 1, 1, nrhs, imat,
510 $ nfail, nerrs, nout )
512 IF( ifact.GE.2 )
THEN
517 CALL sgtt01( n, a, a( m+1 ), a( n+m+1 ), af,
518 $ af( m+1 ), af( n+m+1 ), af( n+2*m+1 ),
519 $ iwork, work, lda, rwork, result( 1 ) )
530 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
531 CALL sgtt02( trans, n, nrhs, a, a( m+1 ),
532 $ a( n+m+1 ), x, lda, work, lda,
537 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
542 CALL sgtt05( trans, n, nrhs, a, a( m+1 ),
543 $ a( n+m+1 ), b, lda, x, lda, xact, lda,
544 $ rwork, rwork( nrhs+1 ), result( 4 ) )
552 IF( result( k ).GE.thresh )
THEN
553 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
554 $
CALL aladhd( nout, path )
555 WRITE( nout, fmt = 9998 )
'SGTSVX', fact, trans,
556 $ n, imat, k, result( k )
563 result( 6 ) = sget06( rcond, rcondc )
564 IF( result( 6 ).GE.thresh )
THEN
565 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
566 $
CALL aladhd( nout, path )
567 WRITE( nout, fmt = 9998 )
'SGTSVX', fact, trans, n,
568 $ imat, k, result( k )
571 nrun = nrun + nt - k1 + 2
580 CALL alasvm( path, nout, nfail, nrun, nerrs )
582 9999
FORMAT( 1x, a,
', N =', i5,
', type ', i2,
', test ', i2,
583 $
', ratio = ', g12.5 )
584 9998
FORMAT( 1x, a,
', FACT=''', a1,
''', TRANS=''', a1,
''', N =',
585 $ i5,
', type ', i2,
', test ', i2,
', ratio = ', g12.5 )
subroutine alasvm(type, nout, nfail, nrun, nerrs)
ALASVM
subroutine aladhd(iounit, path)
ALADHD
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine sgtsv(n, nrhs, dl, d, du, b, ldb, info)
SGTSV computes the solution to system of linear equations A * X = B for GT matrices
subroutine sgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
SGTSVX computes the solution to system of linear equations A * X = B for GT matrices
subroutine sgttrf(n, dl, d, du, du2, ipiv, info)
SGTTRF
subroutine sgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, info)
SGTTRS
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine slagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)
SLAGTM performs a matrix-matrix product of the form C = αAB+βC, where A is a tridiagonal matrix,...
subroutine slarnv(idist, iseed, n, x)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
subroutine slaset(uplo, m, n, alpha, beta, a, lda)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine sscal(n, sa, sx, incx)
SSCAL
subroutine sdrvgt(dotype, nn, nval, nrhs, thresh, tsterr, a, af, b, x, xact, work, rwork, iwork, nout)
SDRVGT
subroutine serrvx(path, nunit)
SERRVX
subroutine sget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
SGET04
subroutine sgtt01(n, dl, d, du, dlf, df, duf, du2, ipiv, work, ldwork, rwork, resid)
SGTT01
subroutine sgtt02(trans, n, nrhs, dl, d, du, x, ldx, b, ldb, resid)
SGTT02
subroutine sgtt05(trans, n, nrhs, dl, d, du, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
SGTT05
subroutine slatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
SLATB4
subroutine slatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
SLATMS