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
sgwvpk

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

     SGWVPK ( Generic segment: Write variable size packets. )

     ENTRY SGWVPK ( HANDLE, NPKTS, PKTSIZ, PKTDAT, NREFS, REFDAT )

Abstract

     Write one or more variable 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
    INTEGER               PKTSIZ ( * )
    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.
     PKTSIZ    I    Array of sizes of variable size packets.
     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.

     PKTSIZ   is the sizes of variable size packets.

              By the size of a packet we mean the number of double
              precision numbers contained in a data packet.

              When writing a segment with variable size packets,
              there must be an element in the array PKTSIZ for each of
              the variable size data packets.

     PKTDAT   is a singly dimensioned array containing the variable
              size data packets to be added to the generic segment
              associated with HANDLE.

              For variable size data packets, PKTDAT will have the
              following structure:

                 Packet #  Range of Locations
                 --------  ------------------------------------------

                    1      PKTDAT(1)           to PKTDAT(P(1))
                    2      PKTDAT(P(1)+1)      to PKTDAT(P(2))
                    3      PKTDAT(P(2)+1)      to PKTDAT(P(3))
                    4      PKTDAT(P(3)+1)      to PKTDAT(P(4))

                                            .
                                            .
                                            .

                   NPKTS   PKTDAT(P(NPKTS-1)+1) to PKTDAT(P(NPKTS))

                               I
                              ---
              where P(I) =    >   PKTSIZ(K).
                              ---
                             K = 1

     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 SGWVPK. 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 be 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 SGWVPK 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 SGWVPK. 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 SGWVPK. On all calls to this subroutine
              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 variable packet sizes
         currently being written, the error SPICE(CALLEDOUTOFORDER)
         is signaled.

     2)  If there is not a generic segment with variable 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 variable 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 explicitly indexed generic segment is being written and
         one or more of the packet sizes is not positive, the error
         SPICE(NONPOSPACKETSIZE) is signaled.

     9)  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.

     10) 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 variable 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 SGBWVS.

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

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

Version

    SPICELIB Version 1.0.1, 27-OCT-2021 (JDR) (NJB)

        Edited the header to comply with NAIF standard. Corrected
        typos in comments.

    SPICELIB Version 1.0.0, 05-APR-1995 (KRG) (WLT)
Fri Dec 31 18:36:48 2021