Program f08lefe

!     F08LEF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: dgbbrd, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
      Character (1), Parameter         :: vect = 'B'
!     .. Local Scalars ..
      Integer                          :: i, info, j, kl, ku, ldab, ldb, ldc,  &
                                          ldpt, ldq, m, n, ncc
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: ab(:,:), b(:,:), c(:,:), d(:), e(:), &
                                          pt(:,:), q(:,:), work(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs, max, min
!     .. Executable Statements ..
      Write (nout,*) 'F08LEF Example Program Results'
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) m, n, kl, ku, ncc
      ldab = kl + ku + 1
      ldb = m
      ldc = m
      ldpt = n
      ldq = m
      Allocate (ab(ldab,n),b(ldb,n),c(m,ncc),d(n),e(n-1),pt(ldpt,n),q(ldq,m),  &
        work(2*m+2*n))

!     Read A from data file

      Read (nin,*)((ab(ku+1+i-j,j),j=max(i-kl,1),min(i+ku,n)),i=1,m)

!     Reduce A to upper bidiagonal form
!     The NAG name equivalent of dgbbrd is f08lef
      Call dgbbrd(vect,m,n,ncc,kl,ku,ab,ldab,d,e,q,ldq,pt,ldpt,c,ldc,work,     &
        info)

!     Print the absolute values of bidiagonal vectors d and e.
!     Any of these can differ by a sign change by combinations of sign
!     changes in columns of Q and P (rows of PT).
      Write (nout,*)
      Write (nout,*) 'Diagonal D:'
      Write (nout,99999) abs(d(1:n))
      Write (nout,*)
      Write (nout,*) 'Off-diagonal E:'
      Write (nout,99999) abs(e(1:n-1))
99999 Format (1X,4(3X,F11.4))

    End Program f08lefe