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
dasec

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

     DASEC  ( DAS extract comments )

     SUBROUTINE DASEC ( HANDLE, BUFSIZ, N, BUFFER, DONE )

Abstract

     Extract comments from the comment area of a binary DAS file.

Required_Reading

     DAS

Keywords

     FILES
     UTILITY

Declarations

     IMPLICIT NONE

     INCLUDE 'das.inc'

     INTEGER               HANDLE
     INTEGER               BUFSIZ
     INTEGER               N
     CHARACTER*(*)         BUFFER(*)
     LOGICAL               DONE

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE     I   Handle of binary DAS file open with read access.
     BUFSIZ     I   Maximum size, in lines, of BUFFER.
     N          O   Number of comments extracted from the DAS file.
     BUFFER     O   Buffer in which extracted comments are placed.
     DONE       O   Indicates whether all comments have been extracted.

Detailed_Input

     HANDLE   is the file handle of a binary DAS file which has been
              opened with read access.

     BUFSIZ   is the maximum number of comments that may be placed into
              BUFFER. This would typically be the declared array size
              for the Fortran character string array passed into this
              routine.

Detailed_Output

     N        is the number of comment lines extracted from the comment
              area of the binary DAS file attached to HANDLE. This
              number will be <= BUFSIZ on output. If N = BUFSIZ and
              DONE <> .TRUE. then there are more comments left to to
              extract. If N = 0, then DONE = .TRUE., i.e., there were
              no comments in the comment area. If there are comments
              in the comment area, or comments remaining after the
              extraction process has begun, N > 0, always.

     BUFFER   is a list of at most BUFSIZ comments which have been
              extracted from the comment area of the binary DAS
              file attached to HANDLE.

     DONE     is a logical flag indicating whether or not all of the
              comment lines from the comment area of the DAS file have
              been read. This variable has the value .TRUE. after the
              last comment line has been read. It will have the value
              .FALSE. otherwise.

              If there are no comments in the comment area, this
              variable will have the value .TRUE., and N = 0.

Parameters

     None.

Exceptions

     1)  If the size of the output line buffer is is not positive,
         the error SPICE(INVALIDARGUMENT) is signaled.

     2)  If a comment line in a DAS file is longer than the length
         of a character string array element of BUFFER, the error
         SPICE(COMMENTTOOLONG) is signaled.

     3)  If there is a mismatch between the number of comment
         characters found and the number of comment characters
         expected, the error SPICE(BADDASCOMMENTAREA) is signaled.

     4)  If the binary DAS file attached to HANDLE is not open for
         reading, an error is signaled by a routine in the call tree of
         this routine.

Files

     See argument HANDLE in $Detailed_Input.

Particulars

     Binary DAS files contain an area which is reserved for storing
     annotations or descriptive textual information describing the data
     contained in a file. This area is referred to as the ``comment
     area'' of the file. The comment area of a DAS file is a line
     oriented medium for storing textual information. The comment
     area preserves any leading or embedded white space in the line(s)
     of text which are stored, so that the appearance of the of
     information will be unchanged when it is retrieved (extracted) at
     some other time. Trailing blanks, however, are NOT preserved,
     due to the way that character strings are represented in
     standard Fortran 77.

     This routine will read the comments from the comment area of
     a binary DAS file, placing them into a line buffer. If the line
     buffer is not large enough to hold the entire comment area,
     the portion read will be returned to the caller, and the DONE
     flag will be set to .FALSE. This allows the comment area to be
     read in ``chunks,'' a buffer at a time. After all of the comment
     lines have been read, the DONE flag will be set to .TRUE.

     This routine can be used to ``simultaneously'' extract comments
     from the comment areas of multiple binary DAS files. See Example
     2 in the $Examples section.

Examples

     Example 1
     ---------

     The following example will extract the entire comment area of a
     binary DAS file attached to HANDLE, displaying the comments on
     the terminal screen.

     Let

        BUFFER  have the following declaration:

           CHARACTER*(80)  BUFFER(25)

        HANDLE  be the handle of an open binary DAS file.

     then

        BUFSIZ = 25
        DONE   = .FALSE.

        DO WHILE ( .NOT. DONE )

           CALL DASEC( HANDLE, BUFSIZ, N, BUFFER, DONE )

           DO I = 1, N

              WRITE (*,*) BUFFER(I)

           END DO

        END DO

     Example 2
     ---------

     The following example demonstrates the use of this routine to
     simultaneously read the comment areas of multiple DAS files.
     For each file, the comments will be displayed on the screen as
     they are extracted.

     Let

        BUFFER  have the following declaration:

           CHARACTER*(80)  BUFFER(25)

        NUMFIL     be the number of binary DAS files that are to have
                   their comment areas displayed.

        DASNAM(I)  Be a list of filenames for the DAS files which are
                   to have their comment areas displayed.

        HANDLE(I)  be a list of handles for the DAS files which are
                   to have their comment areas displayed.

        DONE(I)    be a list of logical flags indicating whether
                   we are done extracting the comment area from the
                   DAS file attached to HANDLE(I)

     then

            BUFSIZ = 25

            DO I = 1, NUMFIL

               DONE(I)   = .FALSE.
               HANDLE(I) = 0

            END DO
     C
     C      Open the DAS files.
     C
            DO I = 1, NUMFIL

               CALL DASOPR ( DASNAM(I), HANDLE(I) )

            END DO
     C
     C      While there are still some comments left to read in at
     C      least one of the files, read them and display them.
     C
            DO WHILE ( .NOT. ALLTRU( DONE, NUMFIL ) )

               DO I = 1, NUMFIL

                  IF ( .NOT. DONE(I) ) THEN

                     WRITE (*,*)
                     WRITE (*,*) 'File: ', DASNAM(I)(:RTRIM(DASNAM(I)))
                     WRITE (*,*)
                     N = 0

                     CALL DASEC ( HANDLE(I),
           .                      BUFSIZ,
           .                      N,
           .                      BUFFER,
           .                      DONE(I) )

                     DO J = 1, N

                        WRITE (*,*) BUFFER(J)(:RTRIM(BUFFER(J)))

                     END DO

                  END IF

               END DO

            END DO

Restrictions

     1)  The comment area may consist only of printing ASCII
         characters, decimal values 32 - 126.

     2)  There is NO maximum length imposed on the significant portion
         of a text line that may be placed into the comment area of a
         DAS file. The maximum length of a line stored in the comment
         area should be kept reasonable, so that they may be easily
         extracted. A good value for this would be 255 characters, as
         this can easily accommodate "screen width" lines as well as
         long lines which may contain some other form of information.

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.4.1, 20-AUG-2021 (JDR)

        Edited the header to comply with NAIF standard. Removed
        reference to non-described parameters from entry #1 in
        $Restrictions section.

    SPICELIB Version 1.4.0, 10-FEB-2017 (NJB)

        Updated to use ZZDDHHLU.

        Now imports parameter FTSIZE from das.inc.

    SPICELIB Version 1.3.0, 18-JUN-1999 (WLT)

        Changed name used in CHKOUT to be consistent with the CHKIN
        value.

    SPICELIB Version 1.2.0, 04-AUG-1994 (KRG)

        Rearranged some of the code to avoid always reading the file
        record. Now we look for the input HANDLE in the file table
        first, and only read the file record if we do not find it. Also
        added a new array to be saved: FILCNT. This is the number of
        comment characters in a file; we save it now rather than
        reading it every time.

        Fixed a bug. If the Fortran character string array elements
        have exactly the same length as a comment in the comment area,
        this routine would halt rather unexpectedly from a memory over
        run.

    SPICELIB Version 1.1.0, 22-NOV-1993 (KRG)

        Changed the value of the parameter FTSIZE from 20 to 21. This
        change makes the value of FTSIZE in DASEC compatible with the
        value in DASFM. See DASFM for a discussion of the reasons for
        the increase in the value.

    SPICELIB Version 1.0.0, 23-NOV-1992 (KRG)
Fri Dec 31 18:36:10 2021