Program e02rbfe

!     E02RBF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: e02raf, e02rbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: l = 4, m = 4, nout = 6
      Integer, Parameter               :: ia = l + 1
      Integer, Parameter               :: ib = m + 1
      Integer, Parameter               :: ic = ia + ib - 1
      Integer, Parameter               :: iw = ib*(2*ib+3)
      Logical, Parameter               :: plot = .False.
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: ans, tval, x
      Integer                          :: i, ifail, nx
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: a(ia), b(ib), cc(ic), w(iw)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs, exp, real
!     .. Executable Statements ..
      If (.Not. plot) Then
        Write (nout,*) 'E02RBF Example Program Results'
        nx = 10
      Else
        nx = 30
      End If

      cc(1) = 1.0E0_nag_wp

      Do i = 1, ic - 1
        cc(i+1) = cc(i)/real(i,kind=nag_wp)
      End Do

      ifail = 0
      Call e02raf(ia,ib,cc,ic,a,b,w,iw,ifail)

      If (.Not. plot) Then
        Write (nout,*)
        Write (nout,*) '    X         Pade          True'
      End If

      Do i = 1, nx
        x = real(i,kind=nag_wp)/10.0_nag_wp

        ifail = 0
        Call e02rbf(a,ia,b,ib,x,ans,ifail)

        tval = exp(x)

        If (plot) Then
          Write (nout,99999) x, ans, tval, abs(tval-ans)/tval
        Else
          Write (nout,99998) x, ans, tval
        End If
      End Do

99999 Format (1X,F6.1,4E19.9)
99998 Format (1X,F6.1,3E15.5)
    End Program e02rbfe