116 SUBROUTINE ddrvrf4( NOUT, NN, NVAL, THRESH, C1, C2, LDC, CRF, A,
117 + LDA, D_WORK_DLANGE )
124 INTEGER LDA, LDC, NN, NOUT
125 DOUBLE PRECISION THRESH
129 DOUBLE PRECISION A( LDA, * ), C1( LDC, * ), C2( LDC, *),
130 + crf( * ), d_work_dlange( * )
136 DOUBLE PRECISION ZERO, ONE
137 parameter( zero = 0.0d+0, one = 1.0d+0 )
139 parameter( ntests = 1 )
142 CHARACTER UPLO, CFORM, TRANS
143 INTEGER I, IFORM, IIK, IIN, INFO, IUPLO, J, K, N,
144 + nfail, nrun, ialpha, itrans
145 DOUBLE PRECISION ALPHA, BETA, EPS, NORMA, NORMC
148 CHARACTER UPLOS( 2 ), FORMS( 2 ), TRANSS( 2 )
149 INTEGER ISEED( 4 ), ISEEDY( 4 )
150 DOUBLE PRECISION RESULT( NTESTS )
153 DOUBLE PRECISION DLAMCH, DLARND, DLANGE
154 EXTERNAL dlamch, dlarnd, dlange
166 COMMON / srnamc / srnamt
169 DATA iseedy / 1988, 1989, 1990, 1991 /
170 DATA uplos /
'U',
'L' /
171 DATA forms /
'N',
'T' /
172 DATA transs /
'N',
'T' /
182 iseed( i ) = iseedy( i )
184 eps = dlamch(
'Precision' )
196 cform = forms( iform )
200 uplo = uplos( iuplo )
204 trans = transs( itrans )
208 IF ( ialpha.EQ. 1)
THEN
211 ELSE IF ( ialpha.EQ. 2)
THEN
214 ELSE IF ( ialpha.EQ. 3)
THEN
218 alpha = dlarnd( 2, iseed )
219 beta = dlarnd( 2, iseed )
229 IF ( itrans.EQ.1 )
THEN
235 a( i, j) = dlarnd( 2, iseed )
239 norma = dlange(
'I', n, k, a, lda,
249 a( i, j) = dlarnd( 2, iseed )
253 norma = dlange(
'I', k, n, a, lda,
265 c1( i, j) = dlarnd( 2, iseed )
273 normc = dlange(
'I', n, n, c1, ldc,
277 CALL dtrttf( cform, uplo, n, c1, ldc, crf,
283 CALL dsyrk( uplo, trans, n, k, alpha, a, lda,
289 CALL dsfrk( cform, uplo, trans, n, k, alpha, a,
295 CALL dtfttr( cform, uplo, n, crf, c2, ldc,
302 c1(i,j) = c1(i,j)-c2(i,j)
311 result(1) = dlange(
'I', n, n, c1, ldc,
313 result(1) = result(1)
314 + / max( abs( alpha ) * norma
315 + + abs( beta ) , one )
316 + / max( n , 1 ) / eps
318 IF( result(1).GE.thresh )
THEN
319 IF( nfail.EQ.0 )
THEN
321 WRITE( nout, fmt = 9999 )
323 WRITE( nout, fmt = 9997 )
'DSFRK',
324 + cform, uplo, trans, n, k, result(1)
337 IF ( nfail.EQ.0 )
THEN
338 WRITE( nout, fmt = 9996 )
'DSFRK', nrun
340 WRITE( nout, fmt = 9995 )
'DSFRK', nfail, nrun
343 9999
FORMAT( 1x,
' *** Error(s) or Failure(s) while testing DSFRK
345 9997
FORMAT( 1x,
' Failure in ',a5,
', CFORM=''',a1,
''',',
346 +
' UPLO=''',a1,
''',',
' TRANS=''',a1,
''',',
' N=',i3,
', K =', i3,
348 9996
FORMAT( 1x,
'All tests for ',a5,
' auxiliary routine passed the ',
349 +
'threshold ( ',i5,
' tests run)')
350 9995
FORMAT( 1x, a6,
' auxiliary routine: ',i5,
' out of ',i5,
351 +
' tests failed to pass the threshold')
subroutine ddrvrf4(nout, nn, nval, thresh, c1, c2, ldc, crf, a, lda, d_work_dlange)
DDRVRF4
subroutine dsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
DSYRK
subroutine dsfrk(transr, uplo, trans, n, k, alpha, a, lda, beta, c)
DSFRK performs a symmetric rank-k operation for matrix in RFP format.
subroutine dtfttr(transr, uplo, n, arf, a, lda, info)
DTFTTR copies a triangular matrix from the rectangular full packed format (TF) to the standard full f...
subroutine dtrttf(transr, uplo, n, a, lda, arf, info)
DTRTTF copies a triangular matrix from the standard full format (TR) to the rectangular full packed f...