SUBROUTINE Get_Deriv ( N, dx, A, AP ) USE Numeric_Kinds_module ! !-------------------------------- Get_Deriv ------------------------------------- ! ! >>> Get_Deriv -- computes a spline derivative of table A into AP ! ! --- on entry the calling routine supplies -- ! ! N -- the number of elements in the A, AP arrays ! dx -- the coordinate spacing between elements in A ! A(N) -- array of function values to get derivs for ! ! --- on exit the routine returns -- ! ! AP(N) -- array of spline-interpolated derivatives ! ! --- information from the following common blocks is used -- ! ! ! !----------------------------- local declarations ----------------------------- ! IMPLICIT NONE ! integer N REAL(KIND=WP_Kind) dx REAL(KIND=WP_Kind) A(N) REAL(KIND=WP_Kind) AP(N) ! REAL(KIND=WP_Kind), allocatable:: x(:) ! stub for x array REAL(KIND=WP_Kind), allocatable:: w(:) ! weight stub REAL(KIND=WP_Kind), allocatable:: abc(:) ! stub for work array ! REAL(KIND=WP_Kind) tab(3) ! spline interp result ! integer IOP(2) ! spline flags integer i ! loop index ! !---------------------------- execution begins here --------------------------- ! allocate(x(N)) allocate(w(N)) allocate(abc(3*N)) do 1 i = 1, N x(i) = i*dx 1 continue ! IOP(1) = 5 IOP(2) = 5 call spl1d1 ( N, x, A, w, IOP, 1, abc, abc(N+1), abc(2*N+1) ) ! do 2 i = 1, N call spl1d2 ( N, x, A, w, 1, x(i), tab ) AP(i) = tab(2) 2 continue deallocate(x) deallocate(w) deallocate(abc) RETURN END SUBROUTINE Get_Deriv