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
dafac

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

     DAFAC ( DAF add comments )

     SUBROUTINE DAFAC ( HANDLE, N, BUFFER )

Abstract

     Add comments from a buffer of character strings to the comment
     area of a binary DAF file, appending them to any comments which
     are already present in the file's comment area.

Required_Reading

     DAF

Keywords

     FILES
     UTILITY

Declarations

     IMPLICIT NONE

     INTEGER               HANDLE
     INTEGER               N
     CHARACTER*(*)         BUFFER(*)

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     HANDLE     I   Handle of a DAF opened with write access.
     N          I   Number of comments to put into the comment area.
     BUFFER     I   Buffer of comments to put into the comment area.

Detailed_Input

     HANDLE   is the file handle of a binary DAF which has been opened
              with write access.

     N        is the number of comments in BUFFER that are to be added
              to the comment area of the binary DAF attached to HANDLE.

     BUFFER   is a buffer containing comments which are to be added
              to the comment area of the binary DAF attached to HANDLE.

Detailed_Output

     None.

Parameters

     None.

Exceptions

     1)  If the number of comments to be added is not positive, the
         error SPICE(INVALIDARGUMENT) is signaled.

     2)  If a non printing ASCII character is encountered in the
         comments, the error SPICE(ILLEGALCHARACTER) is signaled.

     3)  If the binary DAF file attached to HANDLE is not open with
         write access, an error is signaled by a routine in the call
         tree of this routine.

     4)  If the end of the comments cannot be found, i.e., the end of
         comments marker is missing on the last comment record, the
         error SPICE(BADCOMMENTAREA) is signaled.

Files

     See argument HANDLE in $Detailed_Input.

Particulars

     A binary DAF contains a data area which is reserved for storing
     annotations or descriptive textual information about the data
     contained in a file. This area is referred to as the ``comment
     area'' of the file. The comment area of a DAF is a line oriented
     medium for storing textual information. The comment area
     preserves leading or embedded white space in the line(s) of text
     which are stored so that the appearance of the 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 take a buffer of text lines and add (append)
     them to the comment area of a binary DAF. If there are no
     comments in the comment area of the file, then space will be
     allocated and the text lines in BUFFER will be placed into the
     comment area. The text lines may contain only printable ASCII
     characters (decimal values 32 - 126).

     There is NO maximum length imposed on the significant portion
     of a text line that may be placed into the comment area of a
     DAF. The maximum length of a line stored in the comment area
     should be reasonable, however, so that they may be easily
     extracted. A good maximum 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.

Examples

     The numerical results shown for this example may differ across
     platforms. The results depend on the SPICE kernels used as
     input, the compiler and supporting libraries, and the machine
     specific arithmetic implementation.

     1) This example demonstrates how to append new comments to the
        comment area of a DAF file.

        Use the SPK kernel below as input DAF file for the program.

           earthstns_itrf93_201023.bsp


        Example code begins here.


              PROGRAM DAFAC_EX1
              IMPLICIT NONE

        C
        C     SPICELIB functions
        C
              INTEGER               RTRIM

        C
        C     Local parameters
        C
              CHARACTER*(*)         KERNEL
              PARAMETER           ( KERNEL =
             .                         'earthstns_itrf93_201023.bsp' )

              INTEGER               BUFSIZ
              PARAMETER           ( BUFSIZ = 25 )

              INTEGER               CMTSIZ
              PARAMETER           ( CMTSIZ = 7  )

              INTEGER               LINLEN
              PARAMETER           ( LINLEN = 1000 )

        C
        C     Local variables.
        C
              CHARACTER*(LINLEN)    BUFFER ( BUFSIZ )
              CHARACTER*(LINLEN)    NEWCMT ( CMTSIZ )

              INTEGER               HANDLE
              INTEGER               I
              INTEGER               N

              LOGICAL               DONE

        C
        C     Set the new comments to be added to the DAF file.
        C
              DATA                  NEWCMT /
             .  '================== NEW COMMENTS ==================',
             .  '',
             .  '   New comments can be appended to the end of the',
             .  '   comment area of a DAF file, with a single',
             .  '   operation.',
             .  '',
             .  '================ END NEW COMMENTS ================' /


        C
        C     Open a DAF for write. Return a HANDLE referring to the
        C     file.
        C
              CALL DAFOPW ( KERNEL, HANDLE )

        C
        C     Print the end of comment area from the DAF file.
        C     (Maximum 15 lines.)
        C
              DONE = .FALSE.

              DO WHILE ( .NOT. DONE )

                 CALL DAFEC  ( HANDLE, 15, N, BUFFER, DONE )

                 IF ( DONE ) THEN

                    WRITE(*,'(A)') 'End of comment area of input '
             .                  // 'DAF file (max. 15 lines): '
                    WRITE(*,'(A)') '-------------------------------'
             .                  // '-------------------------------'

                    DO I = 1, N

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

                    END DO

                    WRITE(*,'(A)') '-------------------------------'
             .                  // '-------------------------------'

                 END IF

              END DO

        C
        C     Append the new comments to the DAF file.
        C
              CALL DAFAC ( HANDLE, CMTSIZ, NEWCMT )

        C
        C     Safely close the DAF.
        C
              CALL DAFCLS ( HANDLE )

        C
        C     Check if the comments have indeed appended.
        C
        C     Open a DAF for read.
        C
              CALL DAFOPR ( KERNEL, HANDLE )
              DONE = .FALSE.

              DO WHILE ( .NOT. DONE )

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

                 IF ( DONE ) THEN

                    WRITE(*,'(A)') 'End of comment area of input '
             .                  // 'DAF file (max. 25 lines): '
                    WRITE(*,'(A)') '-------------------------------'
             .                  // '-------------------------------'

                    DO I = 1, N

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

                    END DO

                    WRITE(*,'(A)') '-------------------------------'
             .                  // '-------------------------------'

                 END IF

              END DO

        C
        C     Safely close the DAF.
        C
              CALL DAFCLS ( HANDLE )

              END


        When this program was executed on a Mac/Intel/gfortran/64-bit
        platform, the output was:


        End of comment area of input DAF file (max. 15 lines):
        --------------------------------------------------------------
            DSS-65_DXYZ       =    (    -0.0100          0.0242     ***
            DSS-65_TOPO_EPOCH =       @2020-OCT-23/00:00
            DSS-65_UP         =       'Z'
            DSS-65_NORTH      =       'X'

         \begintext
        --------------------------------------------------------------
        End of comment area of input DAF file (max. 25 lines):
        --------------------------------------------------------------
            DSS-65_DXYZ       =    (    -0.0100          0.0242     ***
            DSS-65_TOPO_EPOCH =       @2020-OCT-23/00:00
            DSS-65_UP         =       'Z'
            DSS-65_NORTH      =       'X'

         \begintext
         ================== NEW COMMENTS ==================

            New comments can be appended to the end of the
            comment area of a DAF file, with a single
            operation.

         ================ END NEW COMMENTS ================
        --------------------------------------------------------------


        Warning: incomplete output. 2 lines extended past the right
        margin of the header and have been truncated. These lines are
        marked by "***" at the end of each line.

Restrictions

     1)  This routine uses constants that are specific to the ASCII
         character sequence. The results of using this routine with
         a different character sequence are unpredictable.

     2)  This routine is only used to extract records on environments
         whose characters are a single byte in size. Updates to this
         routine and routines in its call tree may be required to
         properly handle other cases.

Literature_References

     None.

Author_and_Institution

     J. Diaz del Rio    (ODC Space)
     K.R. Gehringer     (JPL)
     F.S. Turner        (JPL)

Version

    SPICELIB Version 2.1.0, 25-NOV-2021 (JDR)

        Added IMPLICIT NONE statement.

        Edited the header to comply with NAIF standard.
        Added complete code examples from existing code fragments.

    SPICELIB Version 2.0.0, 16-NOV-2001 (FST)

        Updated this routine to utilize the new handle manager
        interfaces.

    SPICELIB Version 1.0.0, 26-JUL-1994 (KRG)
Fri Dec 31 18:36:06 2021