Program s18gkfe

!     S18GKF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: nag_wp, s18gkf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Complex (Kind=nag_wp)            :: z
      Real (Kind=nag_wp)               :: a, alpha
      Integer                          :: i, ifail, nl
!     .. Local Arrays ..
      Complex (Kind=nag_wp), Allocatable :: b(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs, real, sign
!     .. Executable Statements ..
      Write (nout,*) 'S18GKF Example Program Results'

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

      Read (nin,*) z, a, nl
      Allocate (b(abs(nl)+1))

      ifail = 0
      Call s18gkf(z,a,nl,b,ifail)

      Write (nout,*)
      Write (nout,*) '      Z           A     NL'
      Write (nout,*)
      Write (nout,99999) z, a, nl

      Write (nout,*)
      Write (nout,*) ' Requested values of J_alpha(Z)'
      Write (nout,*)
      Write (nout,*) '     alpha              J_alpha(Z)'

      alpha = a

      Do i = 1, abs(nl) + 1
        Write (nout,99998) alpha, b(i)
        alpha = alpha + sign(1.0E0_nag_wp,real(nl,kind=nag_wp))
      End Do

99999 Format (1X,'( ',F4.1,', ',F4.1,' )',2X,F4.1,I6)
99998 Format (1X,1P,E12.4,3X,'(',E12.4,',',E12.4,' )')
    End Program s18gkfe