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
sgfpkt

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

     SGFPKT ( Generic Segment: Fetch data packets )

     SUBROUTINE SGFPKT ( HANDLE, DESCR, FIRST, LAST, VALUES, ENDS )

Abstract

     Fetch the data packets indexed from FIRST to LAST from the 
     packet partition of a generic segment. The segment is 
     identified by a DAF file handle and segment descriptor.

Required_Reading

     DAF

Keywords

     GENERIC SEGMENTS

Declarations

     IMPLICIT NONE

     INTEGER               HANDLE
     DOUBLE PRECISION      DESCR   ( * )
     INTEGER               FIRST
     INTEGER               LAST
     DOUBLE PRECISION      VALUES  ( * )
     INTEGER               ENDS    ( * )

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE     I   The file handle attached to an open DAF.
     DESCR      I   The descriptor associated with a generic segment.
     FIRST      I   The index of the first data packet to fetch.
     LAST       I   The index of the last data packet to fetch.
     VALUES     O   The data packets that have been fetched.
     ENDS       O   An array of pointers to the ends of the packets.

Detailed_Input

     HANDLE   is the handle of a DAF opened for reading that
              contains the segment described by DESCR.

     DESCR    is the descriptor of the segment with the desired
              constant values. This must be the descriptor for a
              generic segment in the DAF associated with HANDLE.

     FIRST    is the index of the first value to fetch from the
              constants section of the DAF segment described
              by DESCR.

     LAST     is the index of the last value to fetch from the
              constants section of the DAF segment described
              by DESCR

Detailed_Output

     VALUES   is the array of values constructed by concatenating
              requested packets one after the other into
              an array. Pictorially we can represent VALUES
              as:

                 +--------------------------+
                 | first requested packet   |
                 +--------------------------+
                 | second requested packet  |
                 +--------------------------+
                            .
                            .
                            .
                 +--------------------------+
                 | first requested packet   |
                 +--------------------------+

     ENDS     is an array of pointers to the ends of the
              fetched packets.  ENDS(1) gives the index
              of the last item of the first packet fetched.
              ENDS(2) gives the index of the last item of
              the second packet fetched, etc.

Parameters

     This subroutine makes use of parameters defined in the file
     'sgparam.inc'.

Exceptions

     1)  If FIRST is less than 1 or LAST is greater than the number of
         packets, the error SPICE(REQUESTOUTOFBOUNDS) is signaled.

     2)  If LAST is less than FIRST, the error SPICE(REQUESTOUTOFORDER)
         is signaled.

     3)  If the packet directory structure is unrecognized, the error
         SPICE(UNKNOWNPACKETDIR) is signaled. The most likely cause of
         this error is that an upgrade to your version of the SPICE
         toolkit is needed.

Files

     See the description of HANDLE above.

Particulars

     This routine fetches requested packets from a generic
     DAF segment. The two arrays returned have the following
     relationship to one another. The first packet returned
     resides in VALUES between indexes 1 and ENDS(1).  If a
     second packet is returned it resides in VALUES between
     indices ENDS(1)+1 and ENDS(2).  This relations ship is
     repeated so that if I is greater than 1 and at least I
     packets were returned then the I'th packet resides in
     VALUES between index ENDS(I-1) + 1 and ENDS(I).

Examples

     Suppose that you have located a generic DAF segment (as
     identified by the contents of a segment descriptor).  The
     fragment of code below shows how you could fetch packets
     3 through 7 (assuming that many packets are present).
     from the segment.

        Declarations:

        DOUBLE PRECISION   MYPKSZ (<enough room to hold all packets>)

        INTEGER               ENDS  ( 5 )
        INTEGER               MYNPKT

        get the number of packets

        CALL SGMETA ( HANDLE, DESCR, NPKT, MYNPKT )

        finally, fetch the packets from the segment.

        IF ( 7 .LE. MYNPKT ) THEN
           CALL SGFPKT ( HANDLE, DESCR, 3, 7,  MYPKSZ, ENDS )
        END IF

Restrictions

     1)  The segment described by DESCR must be a generic segment,
         otherwise the results of this routine are not predictable.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     K.R. Gehringer     (JPL)
     W.L. Taber         (JPL)
     E.D. Wright        (JPL)

Version

    SPICELIB Version 1.2.1, 26-OCT-2021 (JDR)

        Edited the header to comply with NAIF standard.

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

        Replaced DAFRDA calls with DAFGDA.

    SPICELIB Version 1.1.0, 30-JUL-1996 (KRG) (NJB)

        Found and fixed a bug in the calculation of the beginning
        address for variable length packet fetching. The base address
        for the packet directory was not added into the value. This
        bug went unnoticed because of a bug in SGSEQW, entry SGWES,
        that put absolute addresses into the packet directory rather
        than addresses that were relative to the start of the DAF
        array. The bug in SGSEQW has also been fixed.

    SPICELIB Version 1.0.0, 06-JAN-1994 (KRG) (WLT)
Fri Dec 31 18:36:47 2021