Program e01sgfe
! E01SGF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: e01sgf, e01shf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, liq, lrq, m, n, nq, nw
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: f(:), q(:), qx(:), qy(:), rq(:), &
u(:), v(:), x(:), y(:)
Integer, Allocatable :: iq(:)
! .. Executable Statements ..
Write (nout,*) 'E01SGF Example Program Results'
! Skip heading in data file
Read (nin,*)
! Input the number of data points
Read (nin,*) m
liq = 2*m + 1
lrq = 6*m + 5
Allocate (x(m),y(m),f(m),iq(liq),rq(lrq))
Do i = 1, m
Read (nin,*) x(i), y(i), f(i)
End Do
! Generate the interpolant.
nq = 0
nw = 0
ifail = 0
Call e01sgf(m,x,y,f,nw,nq,iq,liq,rq,lrq,ifail)
! Input the number of evaluation points.
Read (nin,*) n
Allocate (u(n),v(n),q(n),qx(n),qy(n))
Do i = 1, n
Read (nin,*) u(i), v(i)
End Do
! Evaluate the interpolant using E01SHF.
ifail = 0
Call e01shf(m,x,y,f,iq,liq,rq,lrq,n,u,v,q,qx,qy,ifail)
Write (nout,*)
Write (nout,*) ' I U(I) V(I) Q(I)'
Do i = 1, n
Write (nout,99999) i, u(i), v(i), q(i)
End Do
99999 Format (1X,I6,3F10.2)
End Program e01sgfe