!   D02JAF Example Program Text
!   Mark 26.1 Release. NAG Copyright 2016.

    Module d02jafe_mod

!     D02JAF Example Program Module:
!            Parameters and User-defined Routines

!     .. Use Statements ..
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: bc, cf
!     .. Parameters ..
      Integer, Parameter, Public       :: nin = 5, nout = 6
    Contains
      Function cf(j,x)

!       .. Function Return Value ..
        Real (Kind=nag_wp)             :: cf
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: x
        Integer, Intent (In)           :: j
!       .. Executable Statements ..
        If (j==2) Then
          cf = 0.0E0_nag_wp
        Else
          cf = 1.0E0_nag_wp
        End If
        Return
      End Function cf

      Subroutine bc(i,j,rhs)

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: rhs
        Integer, Intent (In)           :: i
        Integer, Intent (Out)          :: j
!       .. Executable Statements ..
        rhs = 0.0E0_nag_wp
        If (i==1) Then
          j = 1
        Else
          j = -1
        End If
        Return
      End Subroutine bc
    End Module d02jafe_mod

    Program d02jafe

!     D02JAF Example Main Program

!     .. Use Statements ..
      Use d02jafe_mod, Only: bc, cf, nin, nout
      Use nag_library, Only: d02jaf, e02akf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: dx, x, x0, x1, y
      Integer                          :: i, ia1, ifail, k1, k1max, kp, kpmax, &
                                          lw, m, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: c(:), w(:)
      Integer, Allocatable             :: iw(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: real
!     .. Executable Statements ..
      Write (nout,*) 'D02JAF Example Program Results'
!     Skip heading in data file
      Read (nin,*)
!     n: order of the differential equation
!     k1: number of coefficients to be returned
!     kp: number of collocation points
      Read (nin,*) n, k1max, kpmax
      lw = 2*(kpmax+n)*(k1max+1) + 7*k1max
      Allocate (iw(k1max),c(k1max),w(lw))
!     x0: left-hand boundary, x1: right-hand boundary.
      Read (nin,*) x0, x1
      Write (nout,*)
      Write (nout,*) ' KP  K1   Chebyshev coefficients'
      Do kp = 10, kpmax, 5
        Do k1 = 4, k1max, 2

!         ifail: behaviour on error exit
!                =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
          ifail = 0
          Call d02jaf(n,cf,bc,x0,x1,k1,kp,c,w,lw,iw,ifail)

          Write (nout,99999) kp, k1, c(1:k1)
        End Do
      End Do
      k1 = 8
      m = 9
      ia1 = 1
      Write (nout,*)
      Write (nout,99998) 'Last computed solution evaluated at', m,             &
        ' equally spaced points'
      Write (nout,*)
      Write (nout,*) '      X         Y'
      dx = (x1-x0)/real(m-1,kind=nag_wp)
      x = x0
      Do i = 1, m
        ifail = 0
        Call e02akf(k1,x0,x1,c,ia1,k1max,x,y,ifail)

        Write (nout,99997) x, y
        x = x + dx
      End Do

99999 Format (1X,2(I3,1X),8F8.4)
99998 Format (1X,A,I5,A)
99997 Format (1X,2F10.4)
    End Program d02jafe