89
   90
   91
   92
   93
   94
   95      INTEGER            LDA, NN, NOUT
   96
   97
   98      INTEGER            NVAL( NN )
   99      COMPLEX            A( LDA, * ), ARF( * ), AP(*), ASAV( LDA, * )
  100
  101
  102
  103
  104
  105      LOGICAL            LOWER, OK1, OK2
  106      CHARACTER          UPLO, CFORM
  107      INTEGER            I, IFORM, IIN, INFO, IUPLO, J, N,
  108     +                   NERRS, NRUN
  109
  110
  111      CHARACTER          UPLOS( 2 ), FORMS( 2 )
  112      INTEGER            ISEED( 4 ), ISEEDY( 4 )
  113
  114
  115      COMPLEX            CLARND
  117
  118
  120
  121
  122      CHARACTER*32       SRNAMT
  123
  124
  125      COMMON             / srnamc / srnamt
  126
  127
  128      DATA               iseedy / 1988, 1989, 1990, 1991 /
  129      DATA               uplos / 'U', 'L' /
  130      DATA               forms / 'N', 'C' /
  131
  132
  133
  134
  135
  136      nrun = 0
  137      nerrs = 0
  138      info = 0
  139      DO 10 i = 1, 4
  140         iseed( i ) = iseedy( i )
  141   10 CONTINUE
  142
  143      DO 120 iin = 1, nn
  144
  145         n = nval( iin )
  146
  147
  148
  149         DO 110 iuplo = 1, 2
  150
  151            uplo = uplos( iuplo )
  152            lower = .true.
  153            IF ( iuplo.EQ.1 ) lower = .false.
  154
  155
  156
  157            DO 100 iform = 1, 2
  158
  159               cform = forms( iform )
  160
  161               nrun = nrun + 1
  162
  163               DO j = 1, n
  164                  DO i = 1, n
  165                     a( i, j) = 
clarnd( 4, iseed )
 
  166                  END DO
  167               END DO
  168
  169               srnamt = 'CTRTTF'
  170               CALL ctrttf( cform, uplo, n, a, lda, arf, info )
 
  171
  172               srnamt = 'CTFTTP'
  173               CALL ctfttp( cform, uplo, n, arf, ap, info )
 
  174
  175               srnamt = 'CTPTTR'
  176               CALL ctpttr( uplo, n, ap, asav, lda, info )
 
  177
  178               ok1 = .true.
  179               IF ( lower ) THEN
  180                  DO j = 1, n
  181                     DO i = j, n
  182                        IF ( a(i,j).NE.asav(i,j) ) THEN
  183                           ok1 = .false.
  184                        END IF
  185                     END DO
  186                  END DO
  187               ELSE
  188                  DO j = 1, n
  189                     DO i = 1, j
  190                        IF ( a(i,j).NE.asav(i,j) ) THEN
  191                           ok1 = .false.
  192                        END IF
  193                     END DO
  194                  END DO
  195               END IF
  196
  197               nrun = nrun + 1
  198
  199               srnamt = 'CTRTTP'
  200               CALL ctrttp( uplo, n, a, lda, ap, info )
 
  201
  202               srnamt = 'CTPTTF'
  203               CALL ctpttf( cform, uplo, n, ap, arf, info )
 
  204
  205               srnamt = 'CTFTTR'
  206               CALL ctfttr( cform, uplo, n, arf, asav, lda, info )
 
  207
  208               ok2 = .true.
  209               IF ( lower ) THEN
  210                  DO j = 1, n
  211                     DO i = j, n
  212                        IF ( a(i,j).NE.asav(i,j) ) THEN
  213                           ok2 = .false.
  214                        END IF
  215                     END DO
  216                  END DO
  217               ELSE
  218                  DO j = 1, n
  219                     DO i = 1, j
  220                        IF ( a(i,j).NE.asav(i,j) ) THEN
  221                           ok2 = .false.
  222                        END IF
  223                     END DO
  224                  END DO
  225               END IF
  226
  227               IF (( .NOT.ok1 ).OR.( .NOT.ok2 )) THEN
  228                  IF( nerrs.EQ.0 ) THEN
  229                     WRITE( nout, * )
  230                     WRITE( nout, fmt = 9999 )
  231                  END IF
  232                  WRITE( nout, fmt = 9998 ) n, uplo, cform
  233                  nerrs = nerrs + 1
  234               END IF
  235
  236  100       CONTINUE
  237  110    CONTINUE
  238  120 CONTINUE
  239
  240
  241
  242      IF ( nerrs.EQ.0 ) THEN
  243         WRITE( nout, fmt = 9997 ) nrun
  244      ELSE
  245         WRITE( nout, fmt = 9996 ) nerrs, nrun
  246      END IF
  247
  248 9999 FORMAT( 1x, ' *** Error(s) while testing the RFP conversion',
  249     +         ' routines ***')
  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 ( ',
  253     +        i5,' tests run)')
  254 9996 FORMAT( 1x, 'RFP conversion routines: ',i5,' out of ',i5,
  255     +        ' error message recorded')
  256
  257      RETURN
  258
  259
  260
complex function clarnd(idist, iseed)
CLARND
subroutine ctfttp(transr, uplo, n, arf, ap, info)
CTFTTP copies a triangular matrix from the rectangular full packed format (TF) to the standard packed...
subroutine ctfttr(transr, uplo, n, arf, a, lda, info)
CTFTTR copies a triangular matrix from the rectangular full packed format (TF) to the standard full f...
subroutine ctpttf(transr, uplo, n, ap, arf, info)
CTPTTF copies a triangular matrix from the standard packed format (TP) to the rectangular full packed...
subroutine ctpttr(uplo, n, ap, a, lda, info)
CTPTTR copies a triangular matrix from the standard packed format (TP) to the standard full format (T...
subroutine ctrttf(transr, uplo, n, a, lda, arf, info)
CTRTTF copies a triangular matrix from the standard full format (TR) to the rectangular full packed f...
subroutine ctrttp(uplo, n, a, lda, ap, info)
CTRTTP copies a triangular matrix from the standard full format (TR) to the standard packed format (T...