IMPLICIT NONE
INTEGER :: i, j
INTEGER(KIND=RSB_BLAS_IDX_KIND) :: istat = 0, res
TYPE(c_ptr),TARGET :: mtxap = c_null_ptr
INTEGER :: a
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: incx = 1
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: incy = 1
REAL(KIND=8),PARAMETER :: alpha = 3
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: nr = 20
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: nc = nr
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: nnz = (nr*(nr+1))/2
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: nrhs = 1
INTEGER(KIND=RSB_IDX_KIND) :: nt = 0
INTEGER :: ic, ir
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: ia(nnz) = (/ (((ir), ic=1,ir), ir=1,nr ) /)
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: ja(nnz) = (/ (((ic), ic=1,ir), ir=1,nr ) /)
REAL(KIND=8),PARAMETER :: va(nnz) = (/ ((1, ic=1,ir), ir=1,nr ) /)
REAL(KIND=8) :: x(nc,nrhs) = reshape((/((1), ic=1,nc*nrhs)/),[nc,nrhs])
REAL(KIND=8),PARAMETER :: cy(nr,nrhs) = reshape((/((alpha+alpha*nr), ir=1,nr*nrhs)/),[nr,nrhs])
REAL(KIND=8) :: y(nr,nrhs) = reshape((/((alpha), ir=1,nr*nrhs)/),[nr,nrhs])
res = 0
IF (res.NE.0) GOTO 9999
IF (istat.NE.0) GOTO 9997
IF (istat.NE.0) print *,"autotuning returned nonzero:", istat &
&," ...did you enable autotuning ?"
IF (istat.NE.0) GOTO 9997
IF (istat.NE.0) GOTO 9997
IF (nt.NE.0) print*,"autotuner chose ",nt," threads"
IF (istat.NE.0) GOTO 9997
DO j = 1, nrhs
CALL usmv(transn,alpha,a,x(:,j),incx,y(:,j),incy,istat)
END DO
IF (istat.NE.0) GOTO 9997
DO j = 1, nrhs
DO i = 1, nr
IF (y(i,j).NE.cy(i,j)) print *, "first check results are not ok"
IF (y(i,j).NE.cy(i,j)) GOTO 9997
END DO
END DO
y(:,:) = alpha
IF (istat.NE.0) GOTO 9997
DO j = 1, nrhs
CALL usmv(transn,alpha,a,x(:,j),incx,y(:,j),incy,istat)
END DO
IF (istat.NE.0) GOTO 9997
DO j = 1, nrhs
DO i = 1, nr
IF (y(i,j).NE.cy(i,j)) print *,"second check results are not ok"
IF (y(i,j).NE.cy(i,j)) GOTO 9997
END DO
END DO
print *, "check results are ok"
GOTO 9998
9997 res = -1
9998 CONTINUE
IF (istat.NE.0) res = -1
9999 CONTINUE
USE iso_c_binding
IMPLICIT NONE
INTEGER(KIND=RSB_IDX_KIND) :: res
INTEGER :: j
INTEGER(KIND=RSB_BLAS_IDX_KIND) :: istat = 0
INTEGER :: a
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: incx = 1
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: incy = 1
COMPLEX(KIND=8),PARAMETER :: alpha = 3
INTEGER(KIND=RSB_IDX_KIND) :: nr
INTEGER(KIND=RSB_IDX_KIND) :: nc
INTEGER(KIND=RSB_IDX_KIND) :: nz
INTEGER(KIND=RSB_IDX_KIND) :: st
INTEGER(KIND=RSB_IDX_KIND),PARAMETER :: nrhs = 4
COMPLEX(KIND=8), ALLOCATABLE, TARGET, DIMENSION(:,:) :: x
COMPLEX(KIND=8), ALLOCATABLE, TARGET, DIMENSION(:,:) :: y
CHARACTER(KIND=C_SIGNED_CHAR,LEN=7),TARGET :: filename = "pd.mtx"//c_null_char
REAL(KIND=C_DOUBLE) :: mvt,mmt,omt
INTEGER(KIND=C_INT),TARGET::izero=0
res = 0
print*,"Read matrix ",filename(1:6)," ",nr,"x",nc,":",nz
IF (st .EQ. 1) print*,"Matrix has no symmetry"
IF (st .EQ. 1) print*,"Matrix is upper symmetric"
IF (st .EQ. 1) print*,"Matrix is upper hermitian"
IF (istat.NE.0) GOTO 9997
WRITE(*,'(a,i0)') "Using NRHS=",nrhs
ALLOCATE( x(nc,nrhs))
ALLOCATE( y(nr,nrhs))
x = 1.0
y = 0.0
DO j = 1, nrhs
CALL usmv(transn,alpha,a,x(:,j),incx,y(:,j),incy,istat)
END DO
IF (istat.NE.0) GOTO 9997
WRITE(*,'(a,e12.4,a)') "Repeated USMV took ",mvt," s"
y = 0.0
IF (istat.NE.0) GOTO 9997
WRITE(*,'(a,e12.4,a)') "A single USMM took ",mmt," s"
WRITE(*,'(a,g11.4,a)')"USMM-to-USMV speed ratio is is ", mvt/mmt, "x"
print*,"Call auto-tuning routine.."
IF (res.NE.0) GOTO 9997
IF (istat.NE.0) GOTO 9997
IF (istat.NE.0) GOTO 9997
print*,"Repeat measurement."
y = 0.0
IF (istat.NE.0) GOTO 9997
WRITE(*,'(a,e12.4,a)') "Tuned USMM took ",omt," s"
WRITE(*,'(a,g11.4,a)')"Tuned-to-untuned speed ratio is is ",mmt/omt,"x"
GOTO 9998
9997 res = -1
9998 CONTINUE
IF (istat.NE.0) res = -1
USE iso_c_binding
IMPLICIT NONE
INTEGER :: passed = 0, failed = 0
INTEGER(KIND=RSB_IDX_KIND) :: res
TYPE(c_ptr),PARAMETER :: eo = c_null_ptr
TYPE(c_ptr),PARAMETER :: io = c_null_ptr
INTEGER(KIND=C_INT),TARGET::ione=1
IF (res.LT.0) failed = failed + 1
IF (res.EQ.0) passed = passed + 1
IF (res.LT.0) failed = failed + 1
IF (res.EQ.0) passed = passed + 1
print *, "FAILED:", failed
print *, "PASSED:", passed
IF (failed .GT. 0) THEN
stop 1
END IF
END PROGRAM