NAG Library Manual, Mark 28.7
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program s22bafe

!     S22BAF Example Program Text

!     Mark 28.7 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: nag_wp, s22baf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a, b, m, x
      Integer                          :: ifail, kx
!     .. Intrinsic Procedures ..
      Intrinsic                        :: real
!     .. Executable Statements ..
      Write (nout,*) 'S22BAF Example Program Results'

      a = 13.6E0_nag_wp
      b = 14.2E0_nag_wp

      Write (nout,99999) 'a    ', 'b    '
      Write (nout,99998)
      Write (nout,99997) a, b
      Write (nout,99998)
      Write (nout,99994) 'x    ', 'M(a,b,x)  ', 'IFAIL    '
      Write (nout,99995)

      Do kx = -5, 5
        x = real(kx,kind=nag_wp) + 0.5E0_nag_wp
        ifail = -1
        Call s22baf(a,b,x,m,ifail)
        Write (nout,99996) x, m, ifail
      End Do

99999 Format (/,2(1X,A14))
99998 Format (2('+--------------'),'+')
99997 Format (2(1X,F13.2,1X))
99996 Format (1X,F10.2,'    ',1X,E13.5,1X,I9)
99995 Format (3('+--------------'),'+')
99994 Format (/,3(1X,A14))
    End Program s22bafe