Example description
    Program s22cafe

!     S22CAF Example Program Text
!     Mark 27.0 Release. NAG Copyright 2019.

!     .. Use Statements ..
      Use nag_library, Only: nag_wp, s22caf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: n = 2, nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a, q
      Integer                          :: ifail, mode, n_order, ordval, parity
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: f(n), f_deriv(n), x(n)
!     .. Executable Statements ..

!     Skip heading in data file
      Read (nin,*)

!     Read in values
      Read (nin,*) q
      Read (nin,*) n_order
      Read (nin,*) x(1), x(2)

      mode = 2
      ifail = 0

      Write (nout,*) 'S22CAF Example Program Results'
      Write (nout,99998) 'parity', 'ordval', 'a', 'x', 'ce_m(x.q)',            &
        'ce_m''(x.q)'

!     Loop over even orders and print values at x=0.0
      parity = 0
      Do ordval = 0, n_order - 1
        Call s22caf(ordval,q,parity,mode,n,x,f,f_deriv,a,ifail)
        Write (nout,99999) parity, ordval, a, x(1), f(1), f_deriv(1)
      End Do

      Write (nout,99998) 'parity', 'ordval', 'a', 'x', 'se_m(x.q)',            &
        'se_m''(x.q)'

!     Print values at x=0.0 for odd orders
      parity = 1
      Do ordval = 1, n_order
        Call s22caf(ordval,q,parity,mode,n,x,f,f_deriv,a,ifail)
        Write (nout,99999) parity, ordval, a, x(1), f(1), f_deriv(1)
      End Do

99999 Format (2I9,2F9.4,2F12.4)
99998 Format (4A9,2A12)

    End Program s22cafe