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
spkw02

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

     SPKW02 ( SPK, write segment, type 2 )

     SUBROUTINE SPKW02 (  HANDLE,  BODY,    CENTER,  FRAME,
    .                     FIRST,   LAST,    SEGID,   INTLEN,
    .                     N,       POLYDG,  CDATA,   BTIME  )

Abstract

     Write a type 2 segment to an SPK file.

Required_Reading

     NAIF_IDS
     SPC
     SPK

Keywords

     EPHEMERIS

Declarations

     IMPLICIT NONE

     INCLUDE 'spk02.inc'

     INTEGER               HANDLE
     INTEGER               BODY
     INTEGER               CENTER
     CHARACTER*(*)         FRAME
     DOUBLE PRECISION      FIRST
     DOUBLE PRECISION      LAST
     CHARACTER*(*)         SEGID
     DOUBLE PRECISION      INTLEN
     INTEGER               N
     INTEGER               POLYDG
     DOUBLE PRECISION      CDATA (*)
     DOUBLE PRECISION      BTIME

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     MAXDEG     P   Maximum degree of Chebyshev expansions.
     TOLSCL     P   Scale factor used to compute time bound tolerance.
     HANDLE     I   Handle of SPK file open for writing.
     BODY       I   NAIF code for ephemeris object.
     CENTER     I   NAIF code for the center of motion of the body.
     FRAME      I   Reference frame name.
     FIRST      I   Start time of interval covered by segment.
     LAST       I   End time of interval covered by segment.
     SEGID      I   Segment identifier.
     INTLEN     I   Length of time covered by logical record.
     N          I   Number of logical records in segment.
     POLYDG     I   Chebyshev polynomial degree.
     CDATA      I   Array of Chebyshev coefficients.
     BTIME      I   Begin time of first logical record.

Detailed_Input

     HANDLE   is the DAF handle of an SPK file to which a type 2
              segment is to be added. The SPK file must be open for
              writing.

     BODY     is the NAIF integer code for an ephemeris object whose
              state relative to another body is described by the
              segment to be created.

     CENTER   is the NAIF integer code for the center of motion of the
              object identified by BODY.

     FRAME    is the NAIF name for a reference frame relative to which
              the state information for BODY is specified.

     FIRST,
     LAST     are the start and stop times of the time interval over
              which the segment defines the state of body.

     SEGID    is the segment identifier. An SPK segment identifier may
              contain up to 40 characters.

     INTLEN   is the length of time, in seconds, covered by each set of
              Chebyshev polynomial coefficients (each logical record).
              Each set of Chebyshev coefficients must cover this fixed
              time interval, INTLEN.

     N        is the number of sets of Chebyshev polynomial
              coefficients for coordinates (number of logical records)
              to be stored in the segment. There is one set of
              Chebyshev coefficients for each time period.

     POLYDG   is the degree of each set of Chebyshev polynomials used
              to represent the ephemeris information. That is, the
              number of Chebyshev coefficients per coordinate minus
              one. POLYDG must not exceed MAXDEG (see $Parameters
              below).

     CDATA    is a time-ordered array of N sets of Chebyshev polynomial
              coefficients to be placed in the segment of the SPK file.
              Each set has size SETSZ = 3*(POLYDG+1). The coefficients
              are stored in CDATA in order as follows:

                 the (POLYDG + 1) coefficients for the first
                 coordinate of the first logical record,

                 the coefficients for the second coordinate,

                 the coefficients for the third coordinate,

                 the coefficients for the first coordinate for
                 the second logical record, ...

                 and so on.

     BTIME    is the begin time (seconds past J2000 TDB) of first set
              of Chebyshev polynomial coefficients (first logical
              record). FIRST is an appropriate value for BTIME.

Detailed_Output

     None.

     The routine writes to the SPK file referred to by HANDLE a type 02
     SPK segment containing the data in CDATA.

     See the $Particulars section for details about the structure of a
     type 02 SPK segment.

Parameters

     See the include file spk02.inc for declarations of the
     parameters described below.

     TOLSCL   is a tolerance scale for coverage gap at endpoints
              of the segment coverage interval.

     MAXDEG   is the maximum allowed degree of the input
              Chebyshev expansions.

Exceptions

     1)  If the number of sets of coefficients is not positive,
         the error SPICE(NUMCOEFFSNOTPOS) is signaled.

     2)  If the interval length is not positive, the error
         SPICE(INTLENNOTPOS) is signaled.

     3)  If the name of the reference frame is not recognized,
         the error SPICE(INVALIDREFFRAME) is signaled.

     4)  If segment stop time is not greater then the begin time,
         the error SPICE(BADDESCRTIMES) is signaled.

     5)  If the start time of the first record exceeds the descriptor
         begin time by more than a computed tolerance, or if the end
         time of the last record precedes the descriptor end time by
         more than a computed tolerance, the error SPICE(COVERAGEGAP)
         is signaled. See the $Parameters section above for a
         description of the tolerance.

     6)  If the input degree POLYDG is less than 0 or greater than
         MAXDEG, the error SPICE(INVALIDDEGREE) is signaled.

     7)  If the last non-blank character of SEGID occurs past index 40,
         or if SEGID contains any nonprintable characters, an error is
         signaled by a routine in the call tree of this routine.

Files

     A new type 2 SPK segment is written to the SPK file attached
     to HANDLE.

Particulars

     This routine writes an SPK type 2 data segment to the designated
     SPK file, according to the format described in the SPK Required
     Reading.

     Each segment can contain data for only one target, central body,
     and reference frame. The Chebyshev polynomial degree and length
     of time covered by each logical record are also fixed. However,
     an arbitrary number of logical records of Chebyshev polynomial
     coefficients can be written in each segment. Minimizing the
     number of segments in an SPK file will help optimize how the SPICE
     system accesses the file.

     The ephemeris data supplied to the type 2 SPK writer is packed
     into an array as a sequence of records. The logical data records
     are stored contiguously:

        +----------+
        | Record 1 |
        +----------+
        | Record 2 |
        +----------+
            ...
        +----------+
        | Record N |
        +----------+

     The contents of an individual record are:

        +--------------------------------------+
        | Coeff set for X position component   |
        +--------------------------------------+
        | Coeff set for Y position component   |
        +--------------------------------------+
        | Coeff set for Z position component   |
        +--------------------------------------+

     Each coefficient set has the structure:

        +--------------------------------------+
        | Coefficient of T_0                   |
        +--------------------------------------+
        | Coefficient of T_1                   |
        +--------------------------------------+
                          ...
        +--------------------------------------+
        | Coefficient of T_POLYDG              |
        +--------------------------------------+

     Where T_n represents the Chebyshev polynomial
     of the first kind of degree n.

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) This example demonstrates how to create an SPK type 2 kernel
        containing only one segment, given a set of Chebyshev
        coefficients and their associated epochs.


        Example code begins here.


              PROGRAM SPKW02_EX1
              IMPLICIT NONE

        C
        C     Local parameters.
        C
              INTEGER               NAMLEN
              PARAMETER           ( NAMLEN = 40 )

        C
        C     Define the segment identifier parameters.
        C
              CHARACTER*(*)         SPK2
              PARAMETER           ( SPK2  = 'spkw02_ex1.bsp' )

              CHARACTER*(*)         REF
              PARAMETER           ( REF    = 'J2000'          )

              INTEGER               BODY
              PARAMETER           ( BODY   = 3  )

              INTEGER               CENTER
              PARAMETER           ( CENTER = 10 )

              INTEGER               CHBDEG
              PARAMETER           ( CHBDEG = 2  )

              INTEGER               NRECS
              PARAMETER           ( NRECS  = 4  )

              INTEGER               RECSIZ
              PARAMETER           ( RECSIZ = 3*(CHBDEG+1) )

        C
        C     Local variables.
        C
              CHARACTER*(NAMLEN)    IFNAME
              CHARACTER*(NAMLEN)    SEGID

              DOUBLE PRECISION      FIRST
              DOUBLE PRECISION      INTLEN
              DOUBLE PRECISION      LAST
              DOUBLE PRECISION      RECRDS ( RECSIZ, NRECS )

              INTEGER               HANDLE
              INTEGER               NCOMCH

        C
        C     Define the coefficients.
        C
              DATA                  RECRDS /
             .                      1.0101D0, 1.0102D0, 1.0103D0,
             .                      1.0201D0, 1.0202D0, 1.0203D0,
             .                      1.0301D0, 1.0302D0, 1.0303D0,
             .                      2.0101D0, 2.0102D0, 2.0103D0,
             .                      2.0201D0, 2.0202D0, 2.0203D0,
             .                      2.0301D0, 2.0302D0, 2.0303D0,
             .                      3.0101D0, 3.0102D0, 3.0103D0,
             .                      3.0201D0, 3.0202D0, 3.0203D0,
             .                      3.0301D0, 3.0302D0, 3.0303D0,
             .                      4.0101D0, 4.0102D0, 4.0103D0,
             .                      4.0201D0, 4.0202D0, 4.0203D0,
             .                      4.0301D0, 4.0302D0, 4.0303D0 /


        C
        C     Set the start and end times of interval covered by
        C     segment, and the length of time covered by logical
        C     record.
        C
              FIRST  = 100.D0
              LAST   = 500.D0
              INTLEN = 100.D0

        C
        C     NCOMCH is the number of characters to reserve for the
        C     kernel's comment area. This example doesn't write
        C     comments, so set to zero.
        C
              NCOMCH = 0

        C
        C     Internal file name and segment ID.
        C
              IFNAME = 'Type 2 SPK internal file name.'
              SEGID  = 'SPK type 2 test segment'

        C
        C     Open a new SPK file.
        C
              CALL SPKOPN( SPK2, IFNAME, NCOMCH, HANDLE )

        C
        C     Write the segment.
        C
              CALL SPKW02 ( HANDLE, BODY,   CENTER, REF,
             .              FIRST,  LAST,   SEGID,  INTLEN,
             .              NRECS,  CHBDEG, RECRDS, FIRST  )

        C
        C     Close the SPK file.
        C
              CALL SPKCLS ( HANDLE )

              END


        When this program is executed, no output is presented on
        screen. After run completion, a new SPK type 2 exists in
        the output directory.

Restrictions

     None.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     B.V. Semenov       (JPL)
     E.D. Wright        (JPL)
     K.S. Zukor         (JPL)

Version

    SPICELIB Version 2.0.1, 20-AUG-2021 (JDR)

        Edited the header to comply with NAIF standard. Added complete
        example code from existing fragment.

        Extended POLYDG and CDATA arguments description to provide the
        size of the Chebyshev polynomials sets. Moved the details of
        the SPK structure from CDATA argument description to
        $Particulars section.

    SPICELIB Version 2.0.0, 18-JAN-2014 (NJB)

        Relaxed test on relationship between the time bounds of the
        input record set (determined by BTIME, INTLEN, and N) and the
        descriptor bounds FIRST and LAST. Now the descriptor bounds
        may extend beyond the time bounds of the record set by a ratio
        computed using the parameter TOLSCL (see $Parameters above for
        details). Added checks on input polynomial degree.

    SPICELIB Version 1.1.0, 30-OCT-2006 (BVS)

        Removed restriction that the input reference frame should be
        inertial by changing the routine that determines the frame ID
        from the name from IRFNUM to NAMFRM.

    SPICELIB Version 1.0.1, 24-AUG-1998 (EDW)

        Changed a 2 to 2.D0 for a double precision computation. Added
        some comments to the header. Corrected spelling mistakes.

    SPICELIB Version 1.0.0, 01-AUG-1995 (KSZ)
Fri Dec 31 18:36:55 2021