119 SUBROUTINE cdrvrf3( NOUT, NN, NVAL, THRESH, A, LDA, ARF, B1, B2,
120 + s_work_clange, c_work_cgeqrf, tau )
128 INTEGER lda, nn, nout
133 REAL s_work_clange( * )
134 COMPLEX a( lda, * ), arf( * ), b1( lda, * ),
136 COMPLEX c_work_cgeqrf( * ), tau( * )
143 parameter( zero = ( 0.0e+0, 0.0e+0 ) ,
144 + one = ( 1.0e+0, 0.0e+0 ) )
146 parameter( ntests = 1 )
149 CHARACTER uplo, cform, diag, trans, side
150 INTEGER i, iform, iim, iin, info, iuplo, j, m, n, na,
151 + nfail, nrun, iside, idiag, ialpha, itrans
156 CHARACTER uplos( 2 ), forms( 2 ), transs( 2 ),
157 + diags( 2 ), sides( 2 )
158 INTEGER iseed( 4 ), iseedy( 4 )
159 REAL result( ntests )
176 common / srnamc / srnamt
179 DATA iseedy / 1988, 1989, 1990, 1991 /
180 DATA uplos /
'U',
'L' /
181 DATA forms /
'N',
'C' /
182 DATA sides /
'L',
'R' /
183 DATA transs /
'N',
'C' /
184 DATA diags /
'N',
'U' /
194 iseed( i ) = iseedy( i )
196 eps =
slamch(
'Precision' )
208 cform = forms( iform )
212 uplo = uplos( iuplo )
216 side = sides( iside )
220 trans = transs( itrans )
224 diag = diags( idiag )
228 IF ( ialpha.EQ. 1)
THEN
230 ELSE IF ( ialpha.EQ. 1)
THEN
233 alpha =
clarnd( 4, iseed )
243 IF ( iside.EQ.1 )
THEN
269 a( i, j) =
clarnd( 4, iseed )
273 IF ( iuplo.EQ.1 )
THEN
279 CALL
cgeqrf( na, na, a, lda, tau,
280 + c_work_cgeqrf, lda,
288 CALL
cgelqf( na, na, a, lda, tau,
289 + c_work_cgeqrf, lda,
299 a( j, j) = a(j,j) *
clarnd( 5, iseed )
305 CALL
ctrttf( cform, uplo, na, a, lda, arf,
313 b1( i, j) =
clarnd( 4, iseed )
314 b2( i, j) = b1( i, j)
322 CALL
ctrsm( side, uplo, trans, diag, m, n,
323 + alpha, a, lda, b1, lda )
329 CALL
ctfsm( cform, side, uplo, trans,
330 + diag, m, n, alpha, arf, b2,
337 b1( i, j) = b2( i, j ) - b1( i, j )
341 result(1) =
clange(
'I', m, n, b1, lda,
344 result(1) = result(1) / sqrt( eps )
345 + / max( max( m, n), 1 )
347 IF( result(1).GE.thresh )
THEN
348 IF( nfail.EQ.0 )
THEN
350 WRITE( nout, fmt = 9999 )
352 WRITE( nout, fmt = 9997 )
'CTFSM',
353 + cform, side, uplo, trans, diag, m,
369 IF ( nfail.EQ.0 )
THEN
370 WRITE( nout, fmt = 9996 )
'CTFSM', nrun
372 WRITE( nout, fmt = 9995 )
'CTFSM', nfail, nrun
376 ' *** Error(s) or Failure(s) while testing CTFSM + ***')
377 9997 format( 1x,
' Failure in ',a5,
', CFORM=''',a1,
''',',
378 +
' SIDE=''',a1,
''',',
' UPLO=''',a1,
''',',
' TRANS=''',a1,
''',',
379 +
' DIAG=''',a1,
''',',
' M=',i3,
', N =', i3,
', test=',g12.5)
380 9996 format( 1x,
'All tests for ',a5,
' auxiliary routine passed the ',
381 +
'threshold ( ',i5,
' tests run)')
382 9995 format( 1x, a6,
' auxiliary routine: ',i5,
' out of ',i5,
383 +
' tests failed to pass the threshold')