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

NAG FL Interface Introduction
Example description
    Program e02bbfe

!     E02BBF Example Program Text

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use nag_library, Only: e02bbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a, b, s, x
      Integer                          :: ifail, j, m, ncap, ncap7, r
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: c(:), lamda(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: real
!     .. Executable Statements ..
      Write (nout,*) 'E02BBF Example Program Results'

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

      Read (nin,*) m
      Read (nin,*) ncap
      ncap7 = ncap + 7
      Allocate (lamda(ncap7),c(ncap7))

      Read (nin,*) lamda(1:ncap7)
      Read (nin,*) c(1:ncap+3)

      a = lamda(4)
      b = lamda(ncap+4)

      Do r = 1, m
        x = (real(m-r,kind=nag_wp)*a+real(r-1,kind=nag_wp)*b)/                 &
          real(m-1,kind=nag_wp)

        ifail = 0
        Call e02bbf(ncap7,lamda,c,x,s,ifail)

        If (r==1) Then
          Write (nout,*)
          Write (nout,*) '  J       LAMDA(J)    B-spline coefficient (J-2)'
          Write (nout,*)

          Do j = 1, ncap7

            If (j<3 .Or. j>ncap+5) Then
              Write (nout,99999) j, lamda(j)
            Else
              Write (nout,99999) j, lamda(j), c(j-2)
            End If

          End Do

          Write (nout,*)
          Write (nout,*) '  R       Argument      Value of cubic spline'
          Write (nout,*)
        End If

        Write (nout,99999) r, x, s
      End Do

99999 Format (1X,I3,F14.4,F21.4)
    End Program e02bbfe