| sgwfpk | 
| Table of contents Procedure
     SGWFPK ( Generic segments: Write fixed size packets. )
     ENTRY SGWFPK ( HANDLE, NPKTS, PKTDAT, NREFS, REFDAT )
Abstract
     Write one or more fixed size data packets to the generic segment
     currently being written to the DAF file associated with HANDLE.
Required_Reading
     DAF
Keywords
     GENERIC SEGMENTS
Declarations
    IMPLICIT NONE
    INTEGER               HANDLE
    INTEGER               NPKTS
    DOUBLE PRECISION      PKTDAT ( * )
    INTEGER               NREFS
    DOUBLE PRECISION      REFDAT ( * )
Brief_I/O
     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE    I    Handle of a DAF file opened with write access.
     NPKTS     I    Number of data packets to write to a segment.
     PKTDAT    I    Array of packet data.
     NREFS     I    Number of reference values.
     REFDAT    I    Reference data.
Detailed_Input
     HANDLE   is the handle of a DAF file opened with write access.
              This is the handle of a file in which a generic segment
              has been started and is currently being written.
     NPKTS    is the number of data packets to write to a segment.
     PKTDAT   is a singly dimensioned array containing the fixed size
              data packets to be added to the segment associated with
              HANDLE.
              For fixed size data packets, PKTDAT will have the
              following structure:
                 Packet #  Range of Locations
                 --------  ------------------------------------------
                    1      PKTDAT(1)              to PKTDAT(PS)
                    2      PKTDAT(PS+1)           to PKTDAT(2*PS)
                    3      PKTDAT(2*PS+1)         to PKTDAT(3*PS)
                    4      PKTDAT(3*PS+1)         to PKTDAT(4*PS)
                                            .
                                            .
                                            .
                   NPKTS   PKTDAT((NPKTS-1)*PS+1) to PKTDAT(NPKTS*PS)
              where PS = PKTSIZ.
     NREFS    is the number of reference values.
              For implicitly indexed packets, NREFS must have a value
              of two (2).
              When writing packets to a segment which uses an implicit
              index type, the value specified by NREFS is used only on
              the first call to SGWFPK. On all subsequent calls to
              these subroutines for a particular implicitly indexed
              segment, the value of NREFS is ignored.
              For explicitly indexed packets, NREFS must be equal to
              NPKTS, i.e., there should ba a reference value for each
              data packet being written to the segment.
              When writing packets to a segment which uses an explicit
              index type, the value specified by NREFS is used on
              every call to SGWFPK and it must be equal to NPKTS.
     REFDAT   is the reference data values.
              For implicitly indexed packets, there must be two (2)
              values. The reference values represent a starting
              reference value and a step size between consecutive
              reference values, respectively.
              In order to avoid, or at least minimize, numerical
              difficulties associated with computing index values for
              generic segments with implicit index types, the value of
              the step size must be an integer, i.e., DINT(REFDAT(2))
              must equal REFDAT(2).
              When writing packets to a segment which uses an implicit
              index type, the values specified by REFDAT are used only
              on the first call to SGWFPK. On all subsequent calls to
              this subroutine for a particular implicitly indexed
              segment, REFDAT is ignored.
              For explicitly indexed packets, there must be NPKTS
              reference values and the values must be in increasing
              order:
                 REFDAT(I) < REFDAT(I+1), I = 1, NPKTS-1
              When writing packets to a segment which uses an explicit
              index type, the values specified by REFDAT are used on
              every call to SGWFPK. On all calls to these subroutines
              after the first, the value of REFDAT(1) must be greater
              than than the value of REFDAT(NPKTS) from the previous
              call. This preserves the ordering of the reference
              values for the entire segment.
Detailed_Output
     None.
Parameters
     This subroutine makes use of parameters defined in the file
     'sgparam.inc'.
Exceptions
     1)  If there are no generic segments with fixed packet sizes
         currently being written, the error SPICE(CALLEDOUTOFORDER) is
         signaled.
     2)  If there is not a generic segment with fixed packet size being
         written to the file associated with HANDLE, the error
         SPICE(SEGMENTNOTFOUND) is signaled.
     3)  If the type of generic segment being written to this file is
         not a fixed packet size generic segment, the error
         SPICE(SEGTYPECONFLICT) is signaled.
     4)  If the number of packets to be written to the generic segment
         is not positive, the error SPICE(NUMPACKETSNOTPOS) is
         signaled.
     5)  If an explicitly indexed generic segment is being written and
         the number of reference values, NREFS, is not equal to the
         number of data packets being written, NPKTS, the error
         SPICE(INCOMPATIBLENUMREF) is signaled.
     6)  If an explicitly indexed generic segment is being written and
         the reference values are not in increasing order, the error
         SPICE(UNORDEREDREFS) is signaled.
     7)  If an explicitly indexed generic segment is being written and
         the first reference value on the second or later additions
         of packets to the generic segment is not greater than the last
         reference value from the previous addition of packets, the
         error SPICE(UNORDEREDREFS) is signaled.
     8)  If an implicitly indexed generic segment is being written and
         the number of reference values, NREFS, is not equal to two (2)
         on the first call to this subroutine for a particular segment,
         the error SPICE(INCOMPATIBLENUMREF) is signaled.
     9)  If an implicitly indexed generic segment is being written and
         the second reference value, the step size used for indexing,
         is not integral, i.e., DINT(REFDAT(2)) .NE. REFDAT(2), the
         error SPICE(REFVALNOTINTEGER) is signaled.
Files
     See HANDLE in the $Detailed_Input section.
Particulars
     This routine will write one or more fixed size data packets to a
     generic segment in the DAF file associated with HANDLE. The
     generic segment must have been started by a call to SGBWFS.
Examples
     See the $Examples section in the header for the main subroutine.
     It contains examples which demonstrate the use of the entry points
     in the generic segments sequential writer. The entry points which
     comprise the generic segments sequential writer must be used
     together in the proper manner. Rather than repeating the examples
     for each entry point they are provided in a single location.
Restrictions
     None.
Literature_References
     None.
Author_and_Institution
     J. Diaz del Rio    (ODC Space)
     K.R. Gehringer     (JPL)
     W.L. Taber         (JPL)
Version
    SPICELIB Version 1.0.1, 03-JUN-2021 (JDR)
        Edited the header to comply with NAIF standard.
    SPICELIB Version 1.0.0, 05-APR-1995 (KRG) (WLT) | 
Fri Dec 31 18:36:48 2021