Example description
    Program f08mdfe

!     F08MDF Example Program Text

!     Mark 27.0 Release. NAG Copyright 2019.

!     .. Use Statements ..
      Use nag_library, Only: dbdsdc, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: info, ldb, ldu, ldvt, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: b(:,:), d(:), e(:), u(:,:), vt(:,:), &
                                          work(:)
      Real (Kind=nag_wp)               :: q(1)
      Integer                          :: iq(1)
      Integer, Allocatable             :: iwork(:)
!     .. Executable Statements ..
      Write (nout,*) 'F08MDF Example Program Results'
      Write (nout,*)
      Flush (nout)
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n
      ldb = n
      ldu = n
      ldvt = n
      Allocate (b(ldb,n),d(n),e(n-1),u(ldu,n),vt(ldvt,n),work(n*(3*n+          &
        4)),iwork(8*n))

!     Read the bidiagonal matrix B from data file, first
!     the diagonal elements, and then the off diagonal elements

      Read (nin,*) d(1:n)
      Read (nin,*) e(1:n-1)

!     Calculate the singular values and left and right singular
!     vectors of B.

!     The NAG name equivalent of dbdsdc is f08mdf
      Call dbdsdc('Upper','I',n,d,e,u,ldu,vt,ldvt,q,iq,work,iwork,info)

      If (info==0) Then
!       Print the singular values of B.

        Write (nout,*) 'Singular values of B:'
        Write (nout,99999) d(1:n)
      Else
        Write (nout,99998) '** F08MDF/DBDSDC failed with INFO = ', info
      End If

99999 Format (1X,4(3X,F11.4))
99998 Format (1X,A,I10)
    End Program f08mdfe