Program d01tefe
!     D01TEF Example Program Text
!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: d01tdf, d01tef, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: n = 4, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: muzero
      Integer                          :: i, ifail
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: a(1:n), abscissae(1:n), b(1:n),      &
                                          c(1:n), mu(0:2*n), weights(1:n)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: real
!     .. Executable Statements ..
      Write (nout,*) 'D01TEF Example Program Results'
      Do i = 0, 2*n
        mu(i) = 0.0_nag_wp
      End Do
      Do i = 0, 2*n, 2
        mu(i) = 2.0_nag_wp/real(i+1,kind=nag_wp)
      End Do

      ifail = 0
      Call d01tef(n,mu,a,b,c,ifail)
      muzero = mu(0)
      Write (nout,*)
      Write (nout,*) '      a         b         c'
      Write (nout,99999)(a(i),b(i),c(i),i=1,n)
99999 Format (1X,3F10.5)

      ifail = 0
      Call d01tdf(n,a,b,c,muzero,weights,abscissae,ifail)
      Write (nout,*)
      Write (6,*) '   weights       abscissae '
      Write (6,99998)(weights(i),abscissae(i),i=1,4)
      Write (nout,*)
99998 Format (1X,F10.5,5X,F10.5)
    End Program d01tefe