Example description
    Program f01bvfe

!     F01BVF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: dsbtrd, dstebz, f01buf, f01bvf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter    :: zero = 0.0_nag_wp
      Integer, Parameter               :: inc1 = 1, nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: abstol
      Integer                          :: i, ifail, info, j, k, lda, ldb, ldv, &
                                          m, m1, m2, m3, ma1, mb1, n, nsplit
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:,:), b(:,:), d(:), e(:), r(:),    &
                                          v(:,:), w(:), work(:)
      Integer, Allocatable             :: iblock(:), isplit(:), iwork(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
      Write (nout,*) 'F01BVF Example Program Results'
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n, ma1, mb1
      lda = ma1
      ldb = mb1
      ldv = ma1 + mb1 - 2
      m3 = 3*ma1 + mb1 - 4
      Allocate (a(lda,n),b(ldb,n),d(n),e(n),r(n),v(ldv,m3),w(m3),work(4*n),    &
        iblock(n),isplit(n),iwork(3*n))
      Read (nin,*)((a(j,i),j=max(1,ma1+1-i),ma1),i=1,n)
      Read (nin,*)((b(j,i),j=max(1,mb1+1-i),mb1),i=1,n)
      k = n/2

!     ifail: behaviour on error exit
!             =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
      ifail = 0
      Call f01buf(n,mb1,k,b,ldb,w,ifail)

      ifail = 0
      Call f01bvf(n,ma1,mb1,m3,k,a,lda,b,ldb,v,ldv,w,ifail)

!     The NAG name equivalent of dsbtrd is f08hef
      Call dsbtrd('N','U',n,ma1-1,a,lda,d,e,w,inc1,work,info)

      abstol = zero
      Read (nin,*) m1, m2

!     The NAG name equivalent of dstebz is f08jjf
      Call dstebz('I','E',n,zero,zero,m1,m2,abstol,d,e,m,nsplit,r,iblock,      &
        isplit,work,iwork,info)

      Write (nout,*)
      Write (nout,*) 'Selected eigenvalues'
      Write (nout,99999) r(1:m)

99999 Format (1X,8F9.4)
    End Program f01bvfe