Program f16eafe

!     F16EAF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: blas_ddot, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: alpha, beta, r
      Integer                          :: conj, i, incx, incy, ix, iy, j, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: x(:), y(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs
!     .. Executable Statements ..
      Write (nout,*) 'F16EAF Example Program Results'
      Write (nout,*)

!     Skip heading in data file.
      Read (nin,*)

!     Accumulate two dot products, set beta=zero initially.
      beta = 0.0_nag_wp

      Do j = 1, 2
!       Read data for dot product.
        Read (nin,*) n
        Read (nin,*) incx, incy
        Allocate (x(1+(n-1)*abs(incx)),y(1+(n-1)*abs(incy)))

        Read (nin,*) alpha

!       Read the vectors x and y and store forwards or backwards
!       as determined by incx (resp. incy).
        If (incx>0) Then
          ix = 1
        Else
          ix = 1 - (n-1)*incx
        End If

        Do i = 1, n
          Read (nin,*) x(ix)
          ix = ix + incx
        End Do

        If (incy>0) Then
          iy = 1
        Else
          iy = 1 - (n-1)*incy
        End If

        Do i = 1, n
          Read (nin,*) y(iy)
          iy = iy + incy
        End Do

!       Compute r = beta*r + alpha*(x^T*y).
!       The NAG name equivalent of blas_ddot is f16eaf.
        Call blas_ddot(conj,n,alpha,x,incx,beta,y,incy,r)

!       Reset beta for accumulation and deallocate x, y.
        beta = 1.0_nag_wp
        Deallocate (x,y)
      End Do

      Write (nout,99999) r

99999 Format (1X,'Accumulated dot product, r = ',F9.4)
    End Program f16eafe