Index of Functions: A  B  C  D  E  F  G  H  I  J  K  L  M  N  O  P  Q  R  S  T  U  V  W  X 
Index Page
polyds

Table of contents
Procedure
Abstract
Required_Reading
Keywords
Declarations
Brief_I/O
Detailed_Input
Detailed_Output
Parameters
Exceptions
Files
Particulars
Examples
Restrictions
Literature_References
Author_and_Institution
Version

Procedure

     POLYDS ( Compute a Polynomial and its Derivatives )

     SUBROUTINE POLYDS ( COEFFS, DEG, NDERIV, T, P )

Abstract

     Compute the value of a polynomial and its first
     NDERIV derivatives at the value T.

Required_Reading

     None.

Keywords

     INTERPOLATION
     MATH
     POLYNOMIAL

Declarations

     IMPLICIT NONE

     DOUBLE PRECISION      COEFFS ( 0:* )
     INTEGER               DEG
     INTEGER               NDERIV
     DOUBLE PRECISION      T
     DOUBLE PRECISION      P      ( 0:* )

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     COEFFS     I   Coefficients of the polynomial to be evaluated.
     DEG        I   Degree of the polynomial to be evaluated.
     NDERIV     I   Number of derivatives to compute.
     T          I   Point to evaluate the polynomial and derivatives
     P          O   Value of polynomial and derivatives.

Detailed_Input

     COEFFS   are the coefficients of the polynomial that is
              to be evaluated. The first element of this array
              should be the constant term, the second element the
              linear coefficient, the third term the quadratic
              coefficient, and so on. The number of coefficients
              supplied should be one more than DEG.

                 F(X) =   COEFFS(1) + COEFFS(2)*X + COEFFS(3)*X^2

                        + COEFFS(4)*X^4 + ... + COEFFS(DEG+1)*X^DEG

     DEG      is the degree of the polynomial to be evaluated. DEG
              should be one less than the number of coefficients
              supplied.

     NDERIV   is the number of derivatives to compute. If NDERIV
              is zero, only the polynomial will be evaluated. If
              NDERIV = 1, then the polynomial and its first
              derivative will be evaluated, and so on. If the value
              of NDERIV is negative, the routine returns
              immediately.

     T        is the point at which the polynomial and its
              derivatives should be evaluated.

Detailed_Output

     P        is an array containing the value of the polynomial and
              its derivatives evaluated at T. The first element of
              the array contains the value of P at T. The second
              element of the array contains the value of the first
              derivative of P at T and so on. The NDERIV + 1'st
              element of the array contains the NDERIV'th derivative
              of P evaluated at T.

Parameters

     None.

Exceptions

     Error free.

     1)  If NDERIV is less than zero, the routine simply returns.

     2)  If the degree of the polynomial is less than 0, the routine
         returns the first NDERIV+1 elements of P set to 0.

Files

     None.

Particulars

     This routine uses the user supplied coefficients (COEFFS)
     to evaluate a polynomial (having these coefficients) and its
     derivatives at the point T. The zero'th derivative of the
     polynomial is regarded as the polynomial itself.

Examples

     The numerical results shown for this example may differ across
     platforms. The results depend on the SPICE kernels used as
     input, the compiler and supporting libraries, and the machine
     specific arithmetic implementation.

     1) For the polynomial

           F(x) = 1 + 3*x + 0.5*x^2 + x^3 + 0.5*x^4 - x^5 + x^6

        the coefficient set

           Degree  coeffs
           ------  ------
           0       1
           1       3
           2       0.5
           3       1
           4       0.5
           5      -1
           6       1

        Compute the value of the polynomial and it's first
        3 derivatives at the value T = 1.0. We expect:

           Derivative Number     T = 1
           ------------------    -----
           F(x)         0        6
           F'(x)        1        10
           F''(x)       2        23
           F'''(x)      3        78


        Example code begins here.


              PROGRAM POLYDS_EX1
              IMPLICIT NONE

        C
        C     Local constants.
        C
              INTEGER               NDERIV
              PARAMETER           ( NDERIV = 3 )

        C
        C     Local variables.
        C
              DOUBLE PRECISION      COEFFS (7)
              DOUBLE PRECISION      P      ( NDERIV + 1 )
              DOUBLE PRECISION      T

              INTEGER               DEG
              INTEGER               I

              DATA                  COEFFS / 1.D0,   3.D0,
             .                               0.5D0,  1.D0,
             .                               0.5D0, -1.D0,
             .                               1.D0          /

              T = 1.D0
              DEG = 6

              CALL POLYDS ( COEFFS, DEG, NDERIV, T, P )

              DO I= 1, NDERIV + 1
                 WRITE(*,*) 'P = ', P(I)
              END DO

              END


        When this program was executed on a Mac/Intel/gfortran/64-bit
        platform, the output was:


         P =    6.0000000000000000
         P =    10.000000000000000
         P =    23.000000000000000
         P =    78.000000000000000

Restrictions

     1)  Depending on the coefficients the user should be careful when
         taking high order derivatives. As the example shows, these
         can get big in a hurry. In general the coefficients of the
         derivatives of a polynomial grow at a rate greater
         than N! (N factorial).

Literature_References

     None.

Author_and_Institution

     J. Diaz del Rio    (ODC Space)
     K.R. Gehringer     (JPL)
     W.L. Taber         (JPL)

Version

    SPICELIB Version 1.2.0, 16-JUL-2021 (JDR)

        Added IMPLICIT NONE statement.

        Updated the header to comply with NAIF standard. Added
        full code example. Updated Exception #2 to properly describe
        the routine's behavior.

    SPICELIB Version 1.1.0, 11-JUL-1995 (KRG)

        Replaced the function calls to DFLOAT with standard conforming
        calls to DBLE.

    SPICELIB Version 1.0.1, 10-MAR-1992 (WLT)

        Comment section for permuted index source lines was added
        following the header.

    SPICELIB Version 1.0.0, 31-JAN-1990 (WLT)
Fri Dec 31 18:36:39 2021