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
ckw06

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

     CKW06 ( CK, Write segment, type 6 )

     SUBROUTINE CKW06 ( HANDLE,  INST,    REF,     AVFLAG,
    .                   FIRST,   LAST,    SEGID,   NMINI,
    .                   NPKTS,   SUBTPS,  DEGRES,  PACKTS,
    .                   RATES,   SCLKDP,  IVLBDS,  SELLST )

Abstract

     Write a type 6 segment to a CK file.

Required_Reading

     CK
     DAF
     NAIF_IDS
     SCLK
     SPC
     TIME

Keywords

     ATTITUDE
     FILES
     POINTING

Declarations

     IMPLICIT NONE

     INCLUDE 'ck06.inc'
     INCLUDE 'ckparam.inc'


     INTEGER               HANDLE
     INTEGER               INST
     CHARACTER*(*)         REF
     LOGICAL               AVFLAG
     DOUBLE PRECISION      FIRST
     DOUBLE PRECISION      LAST
     CHARACTER*(*)         SEGID
     INTEGER               NMINI
     INTEGER               NPKTS  ( * )
     INTEGER               SUBTPS ( * )
     INTEGER               DEGRES ( * )
     DOUBLE PRECISION      PACKTS ( * )
     DOUBLE PRECISION      RATES  ( * )
     DOUBLE PRECISION      SCLKDP ( * )
     DOUBLE PRECISION      IVLBDS ( * )
     LOGICAL               SELLST

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE     I   Handle of a CK file open for writing.
     INST       I   NAIF instrument ID code.
     REF        I   Reference frame name.
     AVFLAG     I   Flag indicating if the segment will contain angular
                    velocity.
     FIRST      I   Start time of interval covered by segment.
     LAST       I   End time of interval covered by segment.
     SEGID      I   Segment identifier.
     NMINI      I   Number of mini-segments.
     NPKTS      I   Array of packet counts of mini-segments.
     SUBTPS     I   Array of segment subtypes of mini-segments.
     DEGRES     I   Array of polynomial degrees of mini-segments.
     PACKTS     I   Array of data packets of mini-segments.
     RATES      I   Nominal SCLK rates in seconds per tick.
     SCLKDP     I   Array of epochs of mini-segments.
     IVLBDS     I   Mini-segment interval bounds.
     SELLST     I   Interval selection flag.
     MAXDEG     P   Maximum allowed degree of interpolating polynomial.

Detailed_Input

     HANDLE   is the handle of a CK file that has been opened
              for writing.


     INST     is a NAIF integer code associated with an
              instrument or spacecraft structure whose
              orientation is described by the segment to be
              created. INST is treated by the SPICE frame
              subsystem as a CK frame class ID (see the
              Frames Required Reading for details).


     AVFLAG   is a logical flag which indicates whether or not
              the segment will contain angular velocity.


     REF      is the NAIF name for a reference frame relative to
              which the pointing (attitude) information for INST
              is specified.

     FIRST,
     LAST     are, respectively, the bounds of the time interval
              over which the segment defines the attitude of
              INST. FIRST and LAST are encoded SCLK times.

              FIRST must be greater than or equal to the first
              mini-segment interval start time; LAST must be
              less than or equal to the last mini-segment
              interval stop time. See the description of IVLBDS
              below.


     SEGID    is the segment identifier. A CK segment
              identifier may contain up to 40 characters.


     NMINI    is the number of mini-segments comprised by
              the input data. Each mini-segment contains data
              that could be stored in a type 5 segment.
              The parameters and data of a mini-segment are:

                 - a packet count
                 - a type 6 subtype
                 - an interpolating polynomial degree
                 - a nominal SCLK rate in seconds/tick
                 - a sequence of type 6 data packets
                 - a sequence of packet epochs

              These inputs are described below.


     NPKTS    is an array of packet counts. The Ith element of
              NPKTS is the packet count of the Ith mini-segment.

              NPKTS has dimension NMINI.


     SUBTPS   is an array of type 6 subtypes. The Ith element of
              SUBTPS is the subtype of the packets associated
              with the Ith mini-segment.

              SUBTPS has dimension NMINI.


     DEGRES   is an array of interpolating polynomial degrees.
              The Ith element of DEGRES is the polynomial degree
              of the packets associated with the Ith
              mini-segment.

              For subtypes 0 and 2, interpolation degrees must be
              equivalent to 3 mod 4, that is, they must be in
              the set

                 { 3, 7, 11, ..., MAXDEG }

              For subtypes 1 and 3, interpolation degrees must
              be odd and must be in the range 1:MAXDEG.

              DEGRES has dimension NMINI.


     PACKTS   is an array of data packets representing the
              orientation of INST relative to the frame REF. The
              packets for a given mini-segment are stored
              contiguously in increasing time order. The order
              of the sets of packets for different mini-segments
              is the same as the order of their corresponding
              mini-segment intervals.

              Each packet contains a SPICE-style quaternion and
              optionally, depending on the segment subtype,
              attitude derivative data, from which a C-matrix
              and an angular velocity vector may be derived.

              See the discussion of quaternion styles in
              $Particulars below.

              The C-matrix CMAT represented by the Ith data
              packet is a rotation matrix that transforms the
              components of a vector expressed in the base frame
              specified by REF to components expressed in the
              instrument fixed frame at the time SCLKDP(I).

              Thus, if a vector V has components x, y, z in the
              base frame, then V has components x', y', z'
              in the instrument fixed frame where:

                 [ x' ]     [          ] [ x ]
                 | y' |  =  |   CMAT   | | y |
                 [ z' ]     [          ] [ z ]

              Attitude derivative information either explicitly
              contained in, or else derived from, PACKTS(I)
              gives the angular velocity of the instrument fixed
              frame at time SCLKDP(I) with respect to the
              reference frame specified by REF.

              The direction of an angular velocity vector gives
              the right-handed axis about which the instrument
              fixed reference frame is rotating. The magnitude
              of the vector is the magnitude of the
              instantaneous velocity of the rotation, in radians
              per second.

              Packet contents and the corresponding
              interpolation methods depend on the segment
              subtype, and are as follows:

                 Subtype 0:  Hermite interpolation, 8-element
                             packets. Quaternion and quaternion
                             derivatives only, no angular
                             velocity vector provided.
                             Quaternion elements are listed
                             first, followed by derivatives.
                             Angular velocity is derived from
                             the quaternions and quaternion
                             derivatives.

                 Subtype 1:  Lagrange interpolation, 4-element
                             packets. Quaternion only. Angular
                             velocity is derived by
                             differentiating the interpolating
                             polynomials.

                 Subtype 2:  Hermite interpolation, 14-element
                             packets. Quaternion and angular
                             velocity vector, as well as
                             derivatives of each, are provided.
                             The quaternion comes first, then
                             quaternion derivatives, then
                             angular velocity and its
                             derivatives.

                 Subtype 3:  Lagrange interpolation, 7-element
                             packets. Quaternion and angular
                             velocity vector provided. The
                             quaternion comes first.

              Angular velocity is always specified relative to
              the base frame.

              Units of the input data are:

                 Quaternions                unitless
                 Quaternion derivatives     1/TDB second
                 Angular velocity           radians/TDB second
                 Angular acceleration       radians/TDB second**2

              For the Hermite subtypes (0 and 2), quaternion
              representations must be selected so that, for
              consecutive quaternions Q(I) and Q(I+1) in a
              mini-segment, the distance between Q and Q(I+1) is
              less than the distance between Q and -Q(I+1). The
              Lagrange subtypes do not have this restriction.


     RATES    is an array of nominal rates of the spacecraft
              clock associated with INST. The Ith element of
              rates is the clock rate for the packets associated
              with the Ith mini-segment. Units are seconds per
              tick. Spacecraft clock rates are used to scale
              angular velocity to radians/second.


     SCLKDP   is an array containing epochs for all input
              mini-segments. The epochs have a one-to-one
              relationship with the packets in the input
              packet array. The epochs are encoded SCLK times.

              The epochs for a given mini-segment are stored
              contiguously in increasing order. The order of the
              sets of epochs for different mini-segments is the
              same as the order of their corresponding
              mini-segment intervals.

              For each mini-segment, "padding" is allowed: the
              sequence of epochs for that mini-segment may start
              before the corresponding mini-segment interval
              start time and end after the corresponding
              mini-segment interval stop time. Padding is used
              to control behavior of interpolating polynomials
              near mini-segment interval boundaries.

              Due to possible use of padding, the elements of
              SCLKDP, taken as a whole, might not be in
              increasing order.


     IVLBDS   is an array of mini-segment interval boundary
              times. This array is a strictly increasing list of
              the mini-segment interval start times, to which
              the end time for the last interval is appended.
              The interval bounds are encoded SCLK times.

              The Ith mini-segment interval is the time
              coverage interval of the Ith mini-segment (see the
              description of NPKTS above).

              For each mini-segment, the corresponding
              mini-segment interval's start time is greater
              than or equal to the mini-segment's first epoch.
              The interval's stop time may exceed the
              mini-segment's last epoch, allowing a single
              coverage gap to exist between a mini-segment's
              last epoch and its interval stop time.

              The "interpolation interval" of the ith
              mini-segment is contained in the ith mini-segment
              interval: the interpolation interval extends from
              IVLBDS(I) to the minimum of IVLBDS(I+1) and the
              last epoch of the mini-segment.

              For each mini-segment interval other than the
              last, the interval's coverage stop time coincides
              with the coverage start time of the next interval.

              IVLBDS has dimension NMINI+1.


     SELLST   is a logical flag indicating to the CK type 6
              segment reader CKR06 how to select the
              mini-segment interval when a request time
              coincides with a time boundary shared by two
              mini-segment intervals. When SELLST ("select
              last") is .TRUE., the later interval is selected;
              otherwise the earlier interval is selected.

Detailed_Output

     None. See $Particulars for a description of the effect of this
     routine.

Parameters

     MAXDEG   is the maximum allowed degree of the interpolating
              polynomial.

              See the INCLUDE file ck06.inc for the value of
              MAXDEG.

Exceptions

     If any of the following exceptions occur, this routine will
     return without creating a new segment.


     1)  If FIRST is greater than LAST, the error
         SPICE(BADDESCRTIMES) is signaled.

     2)  If REF is not a recognized name, the error
         SPICE(INVALIDREFFRAME) is signaled.

     3)  If the last non-blank character of SEGID occurs past index
         40, the error SPICE(SEGIDTOOLONG) is signaled.

     4)  If SEGID contains any nonprintable characters, the error
         SPICE(NONPRINTABLECHARS) is signaled.

     5)  If NMINI is not at least 1, the error SPICE(INVALIDCOUNT)
         is signaled.

     6)  If the elements of the array IVLBDS are not in strictly
         increasing order, the error SPICE(BOUNDSOUTOFORDER) is
         signaled.

     7)  If the first interval start time IVLBDS(1) is greater than
         FIRST, or if the last interval end time IVLBDS(NMINI+1) is
         less than LAST, the error SPICE(COVERAGEGAP) is signaled.

     8)  If any packet count in the array NPKTS is not at least 2, the
         error SPICE(TOOFEWPACKETS) is signaled.

     9)  If any subtype code in the array SUBTPS is not recognized,
         the error SPICE(INVALIDSUBTYPE) is signaled.

     10) If any interpolation degree in the array DEGRES is not at
         least 1 or is greater than MAXDEG, the error
         SPICE(INVALIDDEGREE) is signaled.

     11) If the window size implied by any element of the array DEGRES
         is odd, the error SPICE(BADWINDOWSIZE) is signaled.

     12) If the elements of the array SCLKDP corresponding to a given
         mini-segment are not in strictly increasing order, the error
         SPICE(TIMESOUTOFORDER) is signaled.

     13) If the first epoch of a mini-segment exceeds the start time
         of the associated mini-segment interval, or if the last
         epoch of a mini-segment is less than the interval start
         time, the error SPICE(BOUNDSDISAGREE) is signaled. However,
         the last epoch of a mini-segment may be less than the end
         time of the corresponding mini-segment interval.

     14) If any quaternion has magnitude zero, the error
         SPICE(ZEROQUATERNION) is signaled.

     15) If an error occurs while writing the output segment, the error
         is signaled by a routine in the call tree of this routine.

     16) This routine assumes that the rotation between adjacent
         quaternions that are stored in the same interval has a
         rotation angle of THETA radians, where

            0  <  THETA  <  pi.
               _

         The routines that evaluate the data in the segment produced
         by this routine cannot distinguish between rotations of THETA
         radians, where THETA is in the interval [0, pi), and
         rotations of

            THETA   +   2 * k * pi

         radians, where k is any integer. These "large" rotations will
         yield invalid results when interpolated. The segment creator
         must ensure that the data stored in the segment will not be
         subject to this sort of ambiguity.

     17) For the Hermite subtypes (0 and 2), quaternion
         representations must be selected so that, for consecutive
         quaternions Q(I) and Q(I+1) in a mini-segment, the distance
         between Q and Q(I+1) is less than the distance between Q and
         -Q(I+1).

         If a pair of quaternions violating this condition is found in
         the input array PACKTS, the error SPICE(BADQUATSIGN) is
         signaled.

     18) If any element of the input RATES array is non-positive, the
         error SPICE(INVALIDSCLKRATE) is signaled.

Files

     A new type 6 CK segment is written to the CK file attached
     to HANDLE.

Particulars

     This routine writes a CK type 6 data segment to the open CK
     file according to the format described in the type 6 section of
     the CK Required Reading. The CK file must have been opened with
     write access.


     Quaternion Styles
     -----------------

     There are different "styles" of quaternions used in
     science and engineering applications. Quaternion styles
     are characterized by

     -  The order of quaternion elements

     -  The quaternion multiplication formula

     -  The convention for associating quaternions
        with rotation matrices

     Two of the commonly used styles are

        - "SPICE"

           > Invented by Sir William Rowan Hamilton
           > Frequently used in mathematics and physics textbooks

        - "Engineering"

           > Widely used in aerospace engineering applications


     SPICELIB subroutine interfaces ALWAYS use SPICE quaternions.
     Quaternions of any other style must be converted to SPICE
     quaternions before they are passed to SPICELIB routines.


     Relationship between SPICE and Engineering Quaternions
     ------------------------------------------------------

     Let M be a rotation matrix such that for any vector V,

        M*V

     is the result of rotating V by theta radians in the
     counterclockwise direction about unit rotation axis vector A.
     Then the SPICE quaternions representing M are

        (+/-) (  cos(theta/2),
                 sin(theta/2) A(1),
                 sin(theta/2) A(2),
                 sin(theta/2) A(3)  )

     while the engineering quaternions representing M are

        (+/-) ( -sin(theta/2) A(1),
                -sin(theta/2) A(2),
                -sin(theta/2) A(3),
                 cos(theta/2)       )

     For both styles of quaternions, if a quaternion q represents
     a rotation matrix M, then -q represents M as well.

     Given an engineering quaternion

        QENG   = ( q0,  q1,  q2,  q3 )

     the equivalent SPICE quaternion is

        QSPICE = ( q3, -q0, -q1, -q2 )


     Associating SPICE Quaternions with Rotation Matrices
     ----------------------------------------------------

     Let FROM and TO be two right-handed reference frames, for
     example, an inertial frame and a spacecraft-fixed frame. Let the
     symbols

        V    ,   V
         FROM     TO

     denote, respectively, an arbitrary vector expressed relative to
     the FROM and TO frames. Let M denote the transformation matrix
     that transforms vectors from frame FROM to frame TO; then

        V   =  M * V
         TO         FROM

     where the expression on the right hand side represents left
     multiplication of the vector by the matrix.

     Then if the unit-length SPICE quaternion q represents M, where

        q = (q0, q1, q2, q3)

     the elements of M are derived from the elements of q as follows:

          +-                                                         -+
          |           2    2                                          |
          | 1 - 2*( q2 + q3 )   2*(q1*q2 - q0*q3)   2*(q1*q3 + q0*q2) |
          |                                                           |
          |                                                           |
          |                               2    2                      |
      M = | 2*(q1*q2 + q0*q3)   1 - 2*( q1 + q3 )   2*(q2*q3 - q0*q1) |
          |                                                           |
          |                                                           |
          |                                                   2    2  |
          | 2*(q1*q3 - q0*q2)   2*(q2*q3 + q0*q1)   1 - 2*( q1 + q2 ) |
          |                                                           |
          +-                                                         -+

     Note that substituting the elements of -q for those of q in the
     right hand side leaves each element of M unchanged; this shows
     that if a quaternion q represents a matrix M, then so does the
     quaternion -q.

     To map the rotation matrix M to a unit quaternion, we start by
     decomposing the rotation matrix as a sum of symmetric
     and skew-symmetric parts:

                                        2
        M = [ I  +  (1-cos(theta)) OMEGA  ] + [ sin(theta) OMEGA ]

                     symmetric                   skew-symmetric


     OMEGA is a skew-symmetric matrix of the form

                   +-             -+
                   |  0   -n3   n2 |
                   |               |
         OMEGA  =  |  n3   0   -n1 |
                   |               |
                   | -n2   n1   0  |
                   +-             -+

     The vector N of matrix entries (n1, n2, n3) is the rotation axis
     of M and theta is M's rotation angle. Note that N and theta
     are not unique.

     Let

        C = cos(theta/2)
        S = sin(theta/2)

     Then the unit quaternions Q corresponding to M are

        Q = +/- ( C, S*n1, S*n2, S*n3 )

     The mappings between quaternions and the corresponding rotations
     are carried out by the SPICELIB routines

        Q2M {quaternion to matrix}
        M2Q {matrix to quaternion}

     M2Q always returns a quaternion with scalar part greater than
     or equal to zero.


     SPICE Quaternion Multiplication Formula
     ---------------------------------------

     Given a SPICE quaternion

        Q = ( q0, q1, q2, q3 )

     corresponding to rotation axis A and angle theta as above, we can
     represent Q using "scalar + vector" notation as follows:

        s =   q0           = cos(theta/2)

        v = ( q1, q2, q3 ) = sin(theta/2) * A

        Q = s + v

     Let Q1 and Q2 be SPICE quaternions with respective scalar
     and vector parts s1, s2 and v1, v2:

        Q1 = s1 + v1
        Q2 = s2 + v2

     We represent the dot product of v1 and v2 by

        <v1, v2>

     and the cross product of v1 and v2 by

        v1 x v2

     Then the SPICE quaternion product is

        Q1*Q2 = s1*s2 - <v1,v2>  + s1*v2 + s2*v1 + (v1 x v2)

     If Q1 and Q2 represent the rotation matrices M1 and M2
     respectively, then the quaternion product

        Q1*Q2

     represents the matrix product

        M1*M2

Examples

     Suppose that you have states and are prepared to produce
     a segment of type 6 in a CK file.

     The following code fragment could be used to add the new segment
     to a previously opened CK file attached to HANDLE. The file must
     have been opened with write access.

        C
        C     Create a segment identifier.
        C
              SEGID = 'MY_SAMPLE_CK_TYPE_6_SEGMENT'

        C
        C     Write the segment.
        C
              CALL CKW06 ( HANDLE,  INST,    REF,     AVFLAG,
             .             FIRST,   LAST,    SEGID,   NMINI,
             .             NPKTS,   SUBTPS,  DEGRES,  PACKTS,
             .             RATES,   SCLKDP,  IVLBDS,  SELLST  )

Restrictions

     None.

Literature_References

     None.

Author_and_Institution

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

Version

    SPICELIB Version 2.0.1, 02-JUN-2021 (JDR)

        Edited the header to comply with NAIF standard.

    SPICELIB Version 2.0.0, 11-AUG-2015 (NJB)

        Added check for invalid SCLK rates.

        Corrected error in header $Exceptions section: changed
        subscript N+1 to NMINI+1. Corrected typo in description
        of subtype 2 data. Added mention of angular acceleration
        units.

    SPICELIB Version 1.0.0, 14-MAR-2014 (NJB) (BVS)
Fri Dec 31 18:36:04 2021