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
ckr03

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

     CKR03 ( C-kernel, read pointing record, data type 3 )

     SUBROUTINE CKR03 ( HANDLE, DESCR, SCLKDP, TOL, NEEDAV,
    .                   RECORD, FOUND )

Abstract

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

Required_Reading

     CK
     DAF

Keywords

     POINTING

Declarations

     IMPLICIT NONE

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

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE     I   File handle.
     DESCR      I   Segment descriptor.
     SCLKDP     I   Pointing request time.
     TOL        I   Time tolerance.
     NEEDAV     I   Angular velocity request flag.
     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
              interpolation intervals then the tolerance has no
              effect because pointing will be returned at the
              request time.

              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.

     NEEDAV   is .TRUE. if angular velocity is requested.

Detailed_Output

     RECORD   is the record that CKE03 will evaluate to determine
              the pointing.

              When the request time falls within an interval for
              which linear interpolation is valid, the values of
              the two pointing instances that bracket the request
              time are returned in RECORD as follows:

                 RECORD( 1  ) = Left bracketing SCLK time.

                 RECORD( 2  ) = lq0  \
                 RECORD( 3  ) = lq1   \    Left bracketing
                 RECORD( 4  ) = lq2   /      quaternion.
                 RECORD( 5  ) = lq3  /

                 RECORD( 6  ) = lav1 \     Left bracketing
                 RECORD( 7  ) = lav2       angular velocity
                 RECORD( 8  ) = lav3 /       ( optional )

                 RECORD( 9  ) = Right bracketing SCLK time.

                 RECORD( 10 ) = rq0  \
                 RECORD( 11 ) = rq1   \    Right bracketing
                 RECORD( 12 ) = rq2   /       quaternion.
                 RECORD( 13 ) = rq3  /

                 RECORD( 14 ) = rav1 \     Right bracketing
                 RECORD( 15 ) = rav2       angular velocity
                 RECORD( 16 ) = rav3 /       ( optional )

                 RECORD( 17 ) = pointing request time, SCLKDP.

              The quantities lq0 - lq3 and rq0 - rq3 are the
              components of the quaternions that represent the
              C-matrices associated with the times that bracket
              the requested time.

              The quantities lav1, lav2, lav3 and rav1, rav2, rav3
              are the components of the angular velocity vectors at
              the respective bracketing times. The components of the
              angular velocity vectors are specified relative to
              the inertial reference frame of the segment.

              If the request time does not fall within an
              interpolation interval, but is within TOL of an
              interval endpoint, the values of that pointing
              instance are returned in both parts of RECORD
              ( i.e. RECORD(1-9) and RECORD(10-16) ).

     FOUND    is .TRUE. if a record was found to satisfy the pointing
              request. This occurs when the time for which pointing
              is requested falls inside one of the interpolation
              intervals, or when the request time is within the
              tolerance of an interval endpoint.

Parameters

     None.

Exceptions

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

     2)  If DESCR is not a valid 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 3, as specified in the
         third integer component of the segment descriptor,
         the error SPICE(WRONGDATATYPE) is signaled.

     4)  If angular velocity data was requested but the segment
         contains no such data, the error SPICE(NOAVDATA) is signaled.

Files

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

Particulars

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

     When the time for which pointing was requested falls within an
     interpolation interval, then FOUND will be true and RECORD will
     contain the pointing instances in the segment that bracket the
     request time.  CKE03 will evaluate RECORD to give pointing at
     the request time.

     However, when the request time is not within any of the
     interpolation intervals, then FOUND will be true only if the
     interval endpoint closest to the request time is within the
     tolerance specified by the user. In this case both parts of
     RECORD will contain this closest pointing instance, and CKE03
     will evaluate RECORD to give pointing at the time associated
     with the returned pointing instance.

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 all of the
     segments in a file applicable to the Mars Observer spacecraft bus
     that are of data type 3, for a particular spacecraft clock time.
     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.

           CHARACTER*(20)        SCLKCH
           CHARACTER*(20)        SCTIME
           CHARACTER*(40)        IDENT

           INTEGER               I
           INTEGER               SC
           INTEGER               INST
           INTEGER               HANDLE
           INTEGER               DTYPE
           INTEGER               ICD      (    6 )

           DOUBLE PRECISION      SCLKDP
           DOUBLE PRECISION      TOL
           DOUBLE PRECISION      CLKOUT
           DOUBLE PRECISION      DESCR    (    5 )
           DOUBLE PRECISION      DCD      (    2 )
           DOUBLE PRECISION      RECORD   (   17 )
           DOUBLE PRECISION      CMAT     ( 3, 3 )
           DOUBLE PRECISION      AV       (    3 )

           LOGICAL               NEEDAV
           LOGICAL               FND
           LOGICAL               SFND


           SC     = -94
           INST   = -94000
           DTYPE  =  3
           NEEDAV = .FALSE.

     C
     C     Load the MO SCLK kernel and the C-kernel.
     C
           CALL FURNSH ( 'MO_SCLK.TSC'       )
           CALL DAFOPR ( 'MO_CK.BC',  HANDLE )
     C
     C     Get the spacecraft clock time. Then 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     Use a tolerance of 2 seconds ( half of the nominal
     C     separation between MO pointing instances ).
     C
           CALL SCTIKS ( SC, '0000000002:000', TOL )

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

           FND    = .FALSE.

           DO WHILE ( ( SFND ) .AND. ( .NOT. FND ) )

     C
     C        Get the segment identifier and descriptor.
     C

              CALL DAFGN ( IDENT                 )
              CALL DAFGS ( DESCR                 )
     C
     C        Unpack the segment descriptor into its integer and
     C        double precision components.
     C
              CALL DAFUS ( DESCR, 2, 6, DCD, ICD )

     C
     C        Determine if this segment should be processed.
     C
              IF ( ( INST          .EQ. ICD( 1 ) ) .AND.
          .        ( SCLKDP + TOL  .GE. DCD( 1 ) ) .AND.
          .        ( SCLKDP - TOL  .LE. DCD( 2 ) ) .AND.
          .        ( DTYPE         .EQ. ICD( 3 ) )      ) THEN


                 CALL CKR03 ( HANDLE, DESCR, SCLKDP, TOL, NEEDAV,
          .                   RECORD, FND )

                 IF ( FND ) THEN

                    CALL CKE03 (NEEDAV,RECORD,CMAT,AV,CLKOUT)

                    CALL SCDECD ( SC, CLKOUT, SCTIME )

                    WRITE (*,*)
                    WRITE (*,*) 'Segment identifier: ', IDENT
                    WRITE (*,*)
                    WRITE (*,*) 'Pointing returned for time: ',
          .                      SCTIME
                    WRITE (*,*)
                    WRITE (*,*) 'C-matrix:'
                    WRITE (*,*)
                    WRITE (*,*) ( CMAT(1,I), I = 1, 3 )
                    WRITE (*,*) ( CMAT(2,I), I = 1, 3 )
                    WRITE (*,*) ( CMAT(3,I), I = 1, 3 )
                    WRITE (*,*)

                 END IF

              END IF

              CALL DAFFPA ( SFND )

           END DO

Restrictions

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

     2)  The record returned by this routine is intended to be
         evaluated by CKE03.

Literature_References

     None.

Author_and_Institution

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

Version

    SPICELIB Version 1.1.2, 12-AUG-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.0, 25-NOV-1992 (JML)
Fri Dec 31 18:36:03 2021