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
chbigr

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

     CHBIGR ( Chebyshev expansion integral )

     SUBROUTINE CHBIGR ( DEGP, CP, X2S, X, P, ITGRLP )

Abstract

     Evaluate an indefinite integral of a Chebyshev expansion at a
     specified point X and return the value of the input expansion at
     X as well. The constant of integration is selected to make the
     integral zero when X equals the abscissa value X2S(1).

Required_Reading

     None.

Keywords

     CHEBYSHEV
     EPHEMERIS
     INTEGRAL
     MATH

Declarations

     IMPLICIT NONE

     INTEGER               DEGP
     DOUBLE PRECISION      CP     ( * )
     DOUBLE PRECISION      X2S    ( 2 )
     DOUBLE PRECISION      X
     DOUBLE PRECISION      P
     DOUBLE PRECISION      ITGRLP

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     DEGP       I   Degree of input Chebyshev expansion.
     CP         I   Chebyshev coefficients of input expansion.
     X2S        I   Transformation parameters.
     X          I   Abscissa value of evaluation.
     P          O   Input expansion evaluated at X.
     ITGRLP     O   Integral evaluated at X.

Detailed_Input

     DEGP     is the degree of the input Chebyshev expansion.

     CP       is an array containing the coefficients of the input
              Chebyshev expansion. The coefficient of the I'th
              Chebyshev polynomial is contained in element CP(I+1),
              for I = 0 : DEGP.

     X2S      is an array containing the "transformation parameters"
              of the domain of the expansion. Element X2S(1)
              contains the midpoint of the interval on which the
              input expansion is defined; X2S(2) is one-half of the
              length of this interval; this value is called the
              interval's "radius."

              The input expansion defines a function f(X) on the
              interval

                 [ X2S(1)-X2S(2),  X2S(1)+X2S(2) ]

              as follows:

                 Define S = ( X - X2S(1) ) / X2S(2)


                                   DEGP+1
                                   __
                                   \
                    f(X) = g(S)  = /  CP(k)  T   (S)
                                   --         k-1
                                   k=1


     X        is the abscissa value at which the function defined by
              the input expansion and its integral are to be
              evaluated. Normally X should lie in the closed
              interval

                 [ X2S(1)-X2S(2),  X2S(1)+X2S(2) ]

              See the $Restrictions section below.

Detailed_Output

     P,
     ITGRLP   define S and f(X) as above in the description of the
              input argument X2S. Then P is f(X), and ITGRLP is
              an indefinite integral of f(X), evaluated at X.

              The indefinite integral satisfies

                 d(ITGRLP)/dX     = f(X)

              and

                 ITGRLP( X2S(1) ) = 0

Parameters

     None.

Exceptions

     1)  If the input degree is negative, the error
         SPICE(INVALDDEGREE) is signaled.

     2)  If the input interval radius is non-positive, the error
         SPICE(INVALIDRADIUS) is signaled.

Files

     None.

Particulars

     Let

        T ,  n = 0, ...
         n

     represent the nth Chebyshev polynomial of the first kind:

        T (x) = cos( n*arccos(x) )
         n

     The input coefficients represent the Chebyshev expansion

                       DEGP+1
                       __
                       \
        f(X) = g(S)  = /  CP(k)  T   (S)
                       --         k-1
                       k=1

     where

        S = ( X - X2S(1) ) / X2S(2)

     This routine evaluates and returns the value at X of an
     indefinite integral F(X), where

        dF(X)/dX    = f(X)  for all X in
                            [X2S(1)-X2S(2), X2S(1)+X2S(2)]

        F( X2S(1) ) = 0

     The value at X of the input expansion

        f(X)

     is returned as well.

     Note that numerical problems may result from applying this
     routine to abscissa values outside of the interval defined
     by the input parameters X2S(*). See the $Restrictions section.

     To evaluate Chebyshev expansions and their derivatives, use the
     SPICELIB routines CHBINT or CHBDER.

     This routine supports the SPICELIB SPK type 20 and PCK type 20
     evaluators SPKE20 and PCKE20.

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) Let the domain of a polynomial to be evaluated be the
        closed interval

           [20, 30]

        Let the input expansion represent the polynomial

                             6
           f(X)  = g(S) = 5*S

        where

           S     = (X - 20)/10

        Let F(X) be an indefinite integral of f(X) such that

           F(20) = 0

        Evaluate

           f(30) and F(30)


        Example code begins here.


              PROGRAM CHBIGR_EX1
              IMPLICIT NONE
        C
        C     Local variables
        C
              DOUBLE PRECISION      CP    ( 6 )
              DOUBLE PRECISION      X
              DOUBLE PRECISION      X2S   ( 2 )
              DOUBLE PRECISION      P
              DOUBLE PRECISION      ITGRLP

              INTEGER               DEGP

        C
        C     Let our domain be the interval [10, 30].
        C
              X2S(1) = 20.D0
              X2S(2) = 10.D0

        C
        C     Assign the expansion coefficients.
        C
              DEGP  = 5

              CP(1) = 0.D0
              CP(2) = 3.75D0
              CP(3) = 0.D0
              CP(4) = 1.875D0
              CP(5) = 0.D0
              CP(6) = 0.375D0

        C
        C     Evaluate the function and its integral at X = 30.
        C
              X = 30.D0

              CALL CHBIGR ( DEGP, CP, X2S, X, P, ITGRLP )

        C
        C     We make the change of variables
        C
        C        S(X) = (1/10) * ( X - 20 )
        C
        C     The expansion represents the polynomial
        C
        C                         5
        C        f(X) = g(S) = 6*S
        C
        C     An indefinite integral of the expansion is
        C
        C                                    6
        C        F(X) = G(S) * dX/dS = 10 * S
        C
        C     where G is defined on the interval [-1, 1]. The result
        C     should be (due to the change of variables)
        C
        C          (G(1)  - G(0) ) * dX/dS
        C
        C        = (F(30) - F(20)) * 10
        C
        C        = 10
        C
        C     The value of the expansion at X should be
        C
        C        f(30) = g(1) = 6
        C
              WRITE (*,*) 'ITGRLP = ', ITGRLP
              WRITE (*,*) 'P      = ', P

              END


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


         ITGRLP =    10.000000000000000
         P      =    6.0000000000000000

Restrictions

     1)  The value (X-X2S(1)) / X2S(2) normally should lie within the
         interval -1:1 inclusive, that is, the closed interval
         [-1, 1]. Chebyshev polynomials increase rapidly in magnitude
         as a function of distance of abscissa values from this
         interval.

         In typical SPICE applications, where the input expansion
         represents position, velocity, or orientation, abscissa
         values that map to points outside of [-1, 1] due to round-off
         error will not cause numeric exceptions.

     2)  No checks for floating point overflow are performed.

     3)  Significant accumulated round-off error can occur for input
         expansions of excessively high degree. This routine imposes
         no limits on the degree of the input expansion; users must
         verify that the requested computation provides appropriate
         accuracy.

Literature_References

     [1]  W. Press, B. Flannery, S. Teukolsky and W. Vetterling,
          "Numerical Recipes -- The Art of Scientific Computing,"
          chapter 5.4, "Recurrence Relations and Clenshaw's Recurrence
          Formula," p 161, Cambridge University Press, 1986.

     [2]  "Chebyshev polynomials," Wikipedia, The Free Encyclopedia.
          Retrieved 01:23, November 23, 2013, from
          http://en.wikipedia.org/w/index.php?title=
          Chebyshev_polynomials&oldid=574881046

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)

Version

    SPICELIB Version 1.0.1, 12-AUG-2021 (JDR)

        Edited the header to comply with NAIF standard.
        Corrected error in $Detailed_Input description of CP.

        Fixed range of Chebyshev coefficients of input expansion in
        the description of argument CP in $Detailed_Input.

    SPICELIB Version 1.0.0, 03-DEC-2013 (NJB)
Fri Dec 31 18:36:01 2021