88 SUBROUTINE zdrvrf2( NOUT, NN, NVAL, A, LDA, ARF, AP, ASAV )
99 COMPLEX*16 A( LDA, * ), ARF( * ), AP(*), ASAV( LDA, * )
105 LOGICAL LOWER, OK1, OK2
106 CHARACTER UPLO, CFORM
107 INTEGER I, IFORM, IIN, INFO, IUPLO, J, N,
111 CHARACTER UPLOS( 2 ), FORMS( 2 )
112 INTEGER ISEED( 4 ), ISEEDY( 4 )
125 COMMON / srnamc / srnamt
128 DATA iseedy / 1988, 1989, 1990, 1991 /
129 DATA uplos /
'U',
'L' /
130 DATA forms /
'N',
'C' /
140 iseed( i ) = iseedy( i )
151 uplo = uplos( iuplo )
153 IF ( iuplo.EQ.1 ) lower = .false.
159 cform = forms( iform )
165 a( i, j) = zlarnd( 4, iseed )
170 CALL ztrttf( cform, uplo, n, a, lda, arf, info )
173 CALL ztfttp( cform, uplo, n, arf, ap, info )
176 CALL ztpttr( uplo, n, ap, asav, lda, info )
182 IF ( a(i,j).NE.asav(i,j) )
THEN
190 IF ( a(i,j).NE.asav(i,j) )
THEN
200 CALL ztrttp( uplo, n, a, lda, ap, info )
203 CALL ztpttf( cform, uplo, n, ap, arf, info )
206 CALL ztfttr( cform, uplo, n, arf, asav, lda, info )
212 IF ( a(i,j).NE.asav(i,j) )
THEN
220 IF ( a(i,j).NE.asav(i,j) )
THEN
227 IF (( .NOT.ok1 ).OR.( .NOT.ok2 ))
THEN
228 IF( nerrs.EQ.0 )
THEN
230 WRITE( nout, fmt = 9999 )
232 WRITE( nout, fmt = 9998 ) n, uplo, cform
242 IF ( nerrs.EQ.0 )
THEN
243 WRITE( nout, fmt = 9997 ) nrun
245 WRITE( nout, fmt = 9996 ) nerrs, nrun
248 9999
FORMAT( 1x,
' *** Error(s) while testing the RFP conversion',
250 9998
FORMAT( 1x,
' Error in RFP,conversion routines N=',i5,
251 +
' UPLO=''', a1,
''', FORM =''',a1,
'''')
252 9997
FORMAT( 1x,
'All tests for the RFP conversion routines passed (',
254 9996
FORMAT( 1x,
'RFP conversion routines:',i5,
' out of ',i5,
255 +
' error message recorded')
subroutine ztfttp(transr, uplo, n, arf, ap, info)
ZTFTTP copies a triangular matrix from the rectangular full packed format (TF) to the standard packed...
subroutine ztfttr(transr, uplo, n, arf, a, lda, info)
ZTFTTR copies a triangular matrix from the rectangular full packed format (TF) to the standard full f...
subroutine ztpttf(transr, uplo, n, ap, arf, info)
ZTPTTF copies a triangular matrix from the standard packed format (TP) to the rectangular full packed...
subroutine ztpttr(uplo, n, ap, a, lda, info)
ZTPTTR copies a triangular matrix from the standard packed format (TP) to the standard full format (T...
subroutine ztrttf(transr, uplo, n, a, lda, arf, info)
ZTRTTF copies a triangular matrix from the standard full format (TR) to the rectangular full packed f...
subroutine ztrttp(uplo, n, a, lda, ap, info)
ZTRTTP copies a triangular matrix from the standard full format (TR) to the standard packed format (T...
subroutine zdrvrf2(nout, nn, nval, a, lda, arf, ap, asav)
ZDRVRF2