e02bcfe.f90

 Program e02bcfe
! E02BCF Example Program Text
! Mark 31.1 Release. nAG Copyright 2025.
! .. Use Statements ..
 Use nag_library, Only: e02bcf, nag_wp
! .. Implicit None Statement ..
 Implicit None
! .. Parameters ..
 Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
 Real (Kind=nag_wp) :: x
 Integer :: i, ifail, l, left, m, ncap, ncap7
! .. Local Arrays ..
 Real (Kind=nag_wp), Allocatable :: c(:), lamda(:)
 Real (Kind=nag_wp) :: s(4)
! .. Executable Statements ..
 Write (nout,*) 'E02BCF Example Program Results'
! Skip heading in data file
 Read (nin,*)
 Read (nin,*) ncap, m
 ncap7 = ncap + 7
 Allocate (lamda(ncap7),c(ncap7))
 Read (nin,*) lamda(1:ncap7)
 Read (nin,*) c(1:(ncap+3))
 Do i = 1, m
 Read (nin,*) x
 Do left = 1, 2
 ifail = 0
 Call e02bcf(ncap7,lamda,c,x,left,s,ifail)
 If (left==1) Then
 If (i==1) Then
 Write (nout,*)
 Write (nout,*) &
 ' X Spline 1st deriv 2nd deriv ', &
 '3rd deriv'
 End If
 Write (nout,*)
 Write (nout,99999) x, ' LEFT', (s(l),l=1,4)
 Else
 Write (nout,99999) x, ' RIGHT', (s(l),l=1,4)
 End If
 End Do
 End Do
99999 Format (1X,E10.2,A,4E12.4)
 End Program e02bcfe

AltStyle によって変換されたページ (->オリジナル) /