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
ckr02

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

     CKR02 ( C-kernel, read pointing record, data type 2 )

     SUBROUTINE CKR02 ( HANDLE, DESCR, SCLKDP, TOL, RECORD, FOUND )

Abstract

     Read a pointing record from a CK segment, data type 2.

Required_Reading

     CK
     DAF

Keywords

     POINTING

Declarations

     IMPLICIT NONE

     INTEGER               HANDLE
     DOUBLE PRECISION      DESCR  ( * )
     DOUBLE PRECISION      SCLKDP
     DOUBLE PRECISION      TOL
     DOUBLE PRECISION      RECORD ( * )
     LOGICAL               FOUND

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE     I   File handle.
     DESCR      I   Segment descriptor.
     SCLKDP     I   Spacecraft clock time.
     TOL        I   Time tolerance
     RECORD     O   Pointing data record.
     FOUND      O   .TRUE. when data is found.

Detailed_Input

     HANDLE   is the integer handle of the CK file containing the
              segment.

     DESCR    is the descriptor of the segment.

     SCLKDP   is the encoded spacecraft clock time for which
              pointing is being requested.

     TOL      is a time tolerance, measured in the same units as
              encoded spacecraft clock.

              When SCLKDP falls within the bounds of one of the
              intervals then the tolerance has no effect. However,
              if the request time is not in one of the intervals
              then the tolerance is used to determine if pointing
              at one of the interval endpoints should be returned.

Detailed_Output

     RECORD   is the pointing record. Contents are as follows:

                 RECORD( 1  ) = Start time of interval.
                 RECORD( 2  ) = Time for which pointing was found.
                 RECORD( 3  ) = Seconds per tick rate.

                 RECORD( 4  ) = q0
                 RECORD( 5  ) = q1
                 RECORD( 6  ) = q2
                 RECORD( 7  ) = q3

                 RECORD( 8  ) = av1
                 RECORD( 9  ) = av2
                 RECORD( 10 ) = av3

              The quantities q0 - q3 are the components of the
              quaternion that represents the C-matrix associated with
              the start time of the interval. The quantities av1,
              av2, and av3 represent the angular velocity vector of
              the interval. The components of the angular velocity
              vector are specified relative to the inertial reference
              frame of the segment.

     FOUND    is .TRUE. if a record was found to satisfy the pointing
              request.

Parameters

     None.

Exceptions

     1)  If the specified handle does not belong to any file that is
         currently known to be open, an error is signaled by a routine
         in the call tree of this routine.

     2)  If DESCR is not a valid, packed descriptor of a segment in
         the CK file specified by HANDLE, the results of this routine
         are unpredictable.

     3)  If the segment is not of data type 2, as specified in the
         third integer component of the segment descriptor,
         the error SPICE(WRONGDATATYPE) is signaled.

Files

     The file containing the segment is specified by its handle, and
     should be opened for read, either by CKLPF or DAFOPR.

Particulars

     See the CK Required Reading file for a detailed description of
     the structure of a type 2 pointing segment.

     This routine searches a type 2 segment and determines if the
     request for pointing can be satisfied by the segment. If so,
     then it returns information in the array RECORD that CKE02 uses
     to evaluate the pointing at the time for which pointing was found.

     When the time for which pointing was requested falls within one
     of the intervals then the returned time is the same as the
     requested time. However, when the request time is not within any
     of the intervals then the returned time will be the interval
     endpoint closest to the request time, provided that endpoint is
     within the tolerance specified by the user.

Examples

     The CKRnn routines are usually used in tandem with the CKEnn
     routines, which evaluate the record returned by CKRnn to give
     the pointing information and output time.

     The following code fragment searches backwards through a file
     (attached to HANDLE) for all segments applicable to the Voyager 2
     wide angle camera, for a particular spacecraft clock time, that
     are of data types 1 or 2. It then evaluates the pointing for that
     epoch and prints the result.

     The search performed here does not mimic the behavior of the CK
     reader APIs CKGP and CKGPAV, which consider data from multiple CK
     files, when available. See the CK Required reading for details.

           SC     = -32
           INST   = -32002
     C
     C     Load the Voyager 2 spacecraft clock kernel and the C-kernel.
     C
           CALL FURNSH ( 'VGR_SCLK.TSC'        )
           CALL DAFOPR ( 'VGR2_CK.BC',  HANDLE )
     C
     C     Get the spacecraft clock time. Must encode it for use
     C     in the C-kernel.
     C
           WRITE (*,*) 'Enter spacecraft clock time string:'
           READ (*,FMT='(A)') SCLKCH
           CALL SCENCD ( SC, SCLKCH, SCLKDP )

     C
     C     Search backwards from the end of the CK file through all
     C     of the segments.
     C
           CALL DAFBBS ( HANDLE )
           CALL DAFFPA ( SFND   )

           DO WHILE ( SFND )

              CALL DAFGN ( IDENT                 )
              CALL DAFGS ( DESCR                 )
              CALL DAFUS ( DESCR, 2, 6, DCD, ICD )

              IF ( INST          .EQ. ICD( 1 )  .AND.
          .        SCLKDP + TOL  .GE. DCD( 1 )  .AND.
          .        SCLKDP - TOL  .LE. DCD( 2 ) ) THEN

                 DTYPE = ICD ( 3 )

                 IF ( DTYPE .EQ. 1 ) THEN

                    CALL CKR01 ( HANDLE, DESCR, SCLKDP, TOL, NEEDAV,
          .                      RECORD, FOUND                       )

                    IF ( FOUND ) THEN
                       CALL CKE01 ( NEEDAV, RECORD, CMAT, AV, CLKOUT )
                    END IF

                 ELSE  IF ( DTYPE .EQ. 2 ) THEN

                    CALL CKR02 ( HANDLE, DESCR, SCLKDP, TOL,
          .                      RECORD, FOUND )

                    IF ( FOUND ) THEN
                       CALL CKE02 ( NEEDAV, RECORD, CMAT, AV, CLKOUT )
                    END IF

                 END IF

                 IF ( FOUND ) THEN

                    WRITE (*,*) 'Segment descriptor and identifier:'
                    WRITE (*,*) DCD, ICD
                    WRITE (*,*) IDENT

                    WRITE (*,*) 'C-matrix:'
                    WRITE (*,*) CMAT

                 END IF

              END IF

              CALL DAFFPA ( SFND )

           END DO

Restrictions

     1)  The file containing the segment should be opened for read,
         either by CKLPF or DAFOPR.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     J.M. Lynch         (JPL)
     W.L. Taber         (JPL)
     E.D. Wright        (JPL)

Version

    SPICELIB Version 1.1.2, 06-JUL-2021 (NJB) (JDR)

        Updated code example to use backwards search. Added
        note regarding difference between this search and those
        performed by the CK reader APIs CKGP and CKGPAV.

        Edited the header to comply with NAIF standard.

    SPICELIB Version 1.1.1, 22-AUG-2006 (EDW)

        Replaced references to LDPOOL with references
        to FURNSH.

    SPICELIB Version 1.1.0, 07-SEP-2001 (EDW)

        Replaced DAFRDA call with DAFGDA.
        Added IMPLICIT NONE.

    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, 30-AUG-1991 (JML)
Fri Dec 31 18:36:03 2021