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
dafana

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

     DAFANA ( DAF, add new array )

     SUBROUTINE DAFANA ( HANDLE, SUM, NAME, DATA, N )

Abstract

     Add a new array to an existing DAF.

Required_Reading

     DAF

Keywords

     FILES

Declarations

     IMPLICIT NONE

     INCLUDE              'zzddhman.inc'

     INTEGER               HANDLE
     DOUBLE PRECISION      SUM      ( * )
     CHARACTER*(*)         NAME
     DOUBLE PRECISION      DATA     ( * )
     INTEGER               N

     INTEGER               TBSIZE
     PARAMETER           ( TBSIZE =   20  )

Brief_I/O

     VARIABLE  I/O  ENTRY POINTS
     --------  ---  --------------------------------------------------
     HANDLE     I   DAFBNA, DAFCAD
     SUM        I   DAFBNA
     NAME       I   DAFBNA
     DATA       I   DAFADA
     N          I   DAFADA
     TBSIZE     P   DAFANA

Detailed_Input

     HANDLE   is the handle of a DAF opened for write access
              by a previous call to DAFOPW or DAFOPN.

     SUM      is the summary for the array being added.

     NAME     is the name of the array being added.

     DATA     contains all or part of the data in the array.

     N        is the number of elements in DATA.

Detailed_Output

     None.

Parameters

     TBSIZE   is the size of the file table maintained internally
              by DAFANA,  TBSIZE is the maximum number of DAFs
              that can be in use simultaneously by this routine.

Exceptions

     1)  If DAFANA is called directly, the error SPICE(BOGUSENTRY)
         is signaled.

     2)  See entry points DAFBNA, DAFADA, DAFENA, and DAFCAD
         for exceptions specific to those entry points.

Files

     See argument HANDLE, above.

Particulars

     DAFANA serves as an umbrella, allowing data to be shared by its
     entry points:

        DAFBNA         Begin new array.
        DAFADA         Add data to array.
        DAFCAD         Continue adding data.
        DAFENA         End new array.

     The main function of these entry points is to simplify the
     addition of new arrays to existing DAFs.

     An application can add data to a single DAF, or to multiple DAFs,
     simultaneously. In the case of writing to a single DAF, the
     creation of a new array requires four steps:

        1) Open a DAF for write access, using either DAFOPW
           (if the file already exists) or DAFOPN (if it does not).

              CALL DAFOPW ( FNAME, HANDLE )

        2) Begin the new DAF by calling DAFBNA,

              CALL DAFBNA ( HANDLE, SUM, NAME )

        3) Add data to the array by calling DAFADA as many times
           as necessary,

              CALL GET_DATA ( DATA, N, FOUND )

              DO WHILE ( FOUND )
                 CALL DAFADA   ( DATA, N        )
                 CALL GET_DATA ( DATA, N, FOUND )
              END DO

        4) End the array by calling DAFENA,

              CALL DAFENA

     Note that the data can be added in chunks of any size, so long
     as the chunks are ordered correctly.

     In applications that add data to multiple DAFs simultaneously, it
     is necessary to specify which DAF to add data to. The DAFANA
     entry points that allow specification of a DAF via a file handle
     argument are DAFBNA (DAF, begin new array) and DAFCAD (DAF,
     continue adding data).  As in the single-DAF case, arrays are
     started by calls to DAFBNA, and data is added to arrays by calls
     to DAFADA. The last DAF designated by the input file handle
     supplied to DAFBNA or DAFCAD is the `current DAF'. If a
     DAF contains an array started by a call to DAFBNA but not yet
     completed by a call to DAFENA, we call this array the `current
     array' for that DAF. Each call to DAFADA will add data to the
     current array in the current DAF. A call to DAFENA will make the
     current array in the current DAF a permanent addition to that DAF.

     The notion of `current DAF' as discussed here applies only to
     DAFs acted upon by entry points of DAFANA. In DAFFA, there is a
     DAF that is treated as the `current DAF' for searching; there is
     no connection between the DAFs regarded as current by DAFANA and
     DAFFA.

     In the following example, we write data obtained from the routine
     GET_DATA into two separate DAFs. The first N/2 elements of the
     array DATA will be written to the first DAF; the rest of the
     array will be written to the second DAF.


        1) Open the DAFs for write access, using either DAFOPW
           (if the files already exist) or DAFOPN (if they do not).

              CALL DAFOPW ( FNAME1, HANDL1 )
              CALL DAFOPW ( FNAME2, HANDL2 )

        2) Begin the new DAFs by calling DAFBNA,

              CALL DAFBNA ( HANDL1, SUM1, NAME1 )
              CALL DAFBNA ( HANDL2, SUM2, NAME2 )

        3) Add data to the arrays by calling DAFCAD and DAFADA as many
           times as necessary, selecting the file to add data to by
           calling DAFCAD:

              CALL GET_DATA ( DATA, N, FOUND )

              DO WHILE ( FOUND )

                 CALL DAFCAD   ( HANDL1                          )
                 CALL DAFADA   ( DATA,               N/2         )

                 CALL DAFCAD   ( HANDL2                          )
                 CALL DAFADA   ( DATA( N/2 + 1 ),    N - N/2     )

                 CALL GET_DATA ( DATA, N, FOUND )

              END DO

        4) End each array by calling DAFENA, selecting the file
           in which to end the array by calling DAFCAD:

              CALL DAFCAD ( HANDL1 )
              CALL DAFENA

              CALL DAFCAD ( HANDL2 )
              CALL DAFENA

Examples

     The numerical results shown for these examples 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) The following example illustrates one possible way to copy
        an array from one DAF to another, N words at a time.

        Use the CK kernel below as the original DAF file.

           vo2_swu_ck2.bc


        Example code begins here.


              PROGRAM DAFANA_EX1
              IMPLICIT NONE

        C
        C     Local parameters
        C
              INTEGER               MAXNSZ
              PARAMETER           ( MAXNSZ = 1000 )

              INTEGER               MAXND
              PARAMETER           ( MAXND  = 124  )

              INTEGER               MAXNI
              PARAMETER           ( MAXNI  = 250  )

              INTEGER               NWORDS
              PARAMETER           ( NWORDS = 100  )

              INTEGER               MAXSUM
              PARAMETER           ( MAXSUM = 125  )

        C
        C     Local variables.
        C
              CHARACTER*(MAXNSZ)    NAME

              DOUBLE PRECISION      DATA   ( NWORDS )
              DOUBLE PRECISION      DC     ( MAXND  )
              DOUBLE PRECISION      SUM    ( MAXSUM )

              INTEGER               BIDX
              INTEGER               CHUNK
              INTEGER               EIDX
              INTEGER               IC     ( MAXNI  )
              INTEGER               ND
              INTEGER               NI
              INTEGER               ORIGIN
              INTEGER               TARGET

              LOGICAL               FOUND

        C
        C     Open the origin DAF file for reading.
        C
              CALL DAFOPR ( 'vo2_swu_ck2.bc', ORIGIN )

        C
        C     Start forward search in origin DAF.
        C
              CALL DAFBFS ( ORIGIN )

        C
        C     Find the first array in origin DAF.
        C
              CALL DAFFNA ( FOUND  )

        C
        C     Get the summary and name of the current array in the
        C     ORIGIN DAF file
        C
              CALL DAFGS  ( SUM  )
              CALL DAFGN  ( NAME )

        C
        C     Unpack the summary.
        C
              CALL DAFHSF ( ORIGIN, ND, NI )
              CALL DAFUS  ( SUM,    ND, NI, DC, IC )

        C
        C     Open the target DAF file for writing. Use 'CK' as
        C     data type, and reserve no records for comments.
        C
              CALL DAFONW ( 'dafana_ex1.bc', 'CK', ND, NI,
             .              'CK file created for example 1 DAFANA', 0,
             .              TARGET )

        C
        C     Begin a new array in the target DAF file, using the
        C     origin SUM and NAME.
        C
              CALL DAFBNA ( TARGET, SUM, NAME )

        C
        C     Copy the complete array for the first segment of the
        C     origin DAF file.
        C
              BIDX = IC(NI-1)
              EIDX = IC(NI  )

              DO WHILE ( BIDX .LE. EIDX )

                 CHUNK = MIN ( BIDX + NWORDS - 1, EIDX )

                 CALL DAFGDA ( ORIGIN, BIDX, CHUNK, DATA )
                 CALL DAFADA ( DATA,   NWORDS )

                 BIDX = BIDX + NWORDS

              END DO

        C
        C     End the new array in the target DAF.
        C
              CALL DAFENA

        C
        C     Close the DAF files.
        C
              CALL DAFCLS ( ORIGIN )
              CALL DAFCLS ( TARGET )

              END


        When this program is executed, no output is presented on
        screen. After run completion, a new CK file exists in the
        output directory.


     2)  A simple example demonstrating simultaneous addition
         of data to multiple DAFs.

         Assume we have data from a text file containing three
         columns of numbers. We will write the data from each
         column out to a separate DAF.

         To confirm that the DAFs created by this program contain the
         correct contents, we will read the data from each DAF and
         combine it to create a matrix. This matrix should contain
         the same data as the file we assumed to be the source for
         our dataset.

         The format of the output text should be as follows:

            .-                   -.
            |  n11    n12    n13  |
            |  n21    n22    n23  |
            |   .      .      .   |
            |   .      .      .   |
            |   .      .      .   |
            `-                   -'

         where the symbol nij indicates the jth number on the ith line
         of the source data file.


        Example code begins here.


              PROGRAM DAFANA_EX2
              IMPLICIT NONE

        C
        C     Assume we have read columns of d.p. numbers
        C     from a text file. Write the data from each
        C     column into a separate DAF.  Read these DAFs
        C     and create a matrix containing the same data
        C     as assumed input text file.
        C
        C     Since we do not need to retain any descriptive
        C     information about the DAFs inside of the files
        C     themselves, we'll use a summary format having
        C     two integer components (the minimum--these are
        C     reserved for use by the DAF routines) and zero
        C     double precision components.
        C
        C     The internal file names and array names will
        C     simply indicate the data sources.
        C

        C
        C     Local parameters
        C
              INTEGER               FNMLEN
              PARAMETER           ( FNMLEN = 20 )

              INTEGER               LINLEN
              PARAMETER           ( LINLEN = 80 )

              INTEGER               MAXLNS
              PARAMETER           ( MAXLNS =  9 )

              INTEGER               MAXCOL
              PARAMETER           ( MAXCOL =  3 )

              INTEGER               ND
              PARAMETER           ( ND     =  0 )

              INTEGER               NDAF
              PARAMETER           ( NDAF   =  3 )

              INTEGER               NI
              PARAMETER           ( NI     =  2 )

              INTEGER               NUMLEN
              PARAMETER           ( NUMLEN = 30 )

              INTEGER               SIG
              PARAMETER           ( SIG    = 10 )

        C
        C     Local variables
        C
              CHARACTER*(FNMLEN)    DAFNAM ( NDAF   )
              CHARACTER*(FNMLEN)    INFILE
              CHARACTER*(LINLEN)    LINE
              CHARACTER*(NUMLEN)    NUMCH
              CHARACTER*(LINLEN)    PRSERR
              CHARACTER*(FNMLEN)    RESULT

              DOUBLE PRECISION      DC     ( 1      )
              DOUBLE PRECISION      NUMBER ( MAXLNS, MAXCOL )
              DOUBLE PRECISION      NUMDP
              DOUBLE PRECISION      SUMMRY ( 1      )

              INTEGER               FA
              INTEGER               HAN    ( NDAF   )
              INTEGER               I
              INTEGER               IA
              INTEGER               IC     ( NI     )
              INTEGER               J
              INTEGER               LENGTH
              INTEGER               NCOLS
              INTEGER               PTR

              LOGICAL               EOF
              LOGICAL               FOUND

        C
        C     Initial values
        C
              DATA                  DAFNAM   /  'COLUMN1.DAF',
             .                                  'COLUMN2.DAF',
             .                                  'COLUMN3.DAF'  /

              DATA                  NUMBER  /
             .               11.D0, 21.D0, 31.D0, 41.D0, 51.D0,
             .               61.D0, 71.D0, 81.D0, 91.D0,
             .               12.D0, 22.D0, 32.D0, 42.D0, 52.D0,
             .               62.D0, 72.D0, 82.D0, 92.D0,
             .               13.D0, 23.D0, 33.D0, 43.D0, 52.D0,
             .               63.D0, 73.D0, 83.D0, 93.D0        /

        C
        C     Create the new DAFs, and start a new array in each
        C     one.  Just use the file name for the internal file
        C     name and array name, for each DAF.  No assignments
        C     are required for the array summaries.
        C
              DO I = 1, NDAF

                 CALL DAFOPN ( DAFNAM(I), ND, NI,
             .                 DAFNAM(I), 0,  HAN(I) )

                 CALL DAFBNA ( HAN(I), SUMMRY, DAFNAM(I) )

              END DO

        C
        C     At this point, we assume that we have read the
        C     file line by line. Add the numbers from each column
        C     to the corresponding DAF.
        C
              DO I = 1, MAXLNS

        C
        C        Add the number from the ith column to the array
        C        in the ith DAF.  We'll use DAFCAD to select
        C        the correct DAF to add data to.
        C
                 DO J = 1, NDAF
                    CALL DAFCAD ( HAN(J)         )
                    CALL DAFADA ( NUMBER(I,J), 1 )
                 END DO

              END DO

        C
        C     Finish ("end") the arrays.  Again, we'll use DAFCAD
        C     to select the DAFs in which the arrays are to be
        C     finished.  After finishing each array, close the DAF
        C     containing it.
        C
              DO I = 1, NDAF
                 CALL DAFCAD ( HAN(I) )
                 CALL DAFENA
                 CALL DAFCLS ( HAN(I) )
              END DO

        C
        C     Now for the verification step.  We'll try to
        C     print a matrix containing the same data as
        C     the original input file.  The format of the numbers,
        C     the delimiters separating the numbers, spacing, and
        C     non-printing characters may differ.
        C
        C     Open the DAFs for reading.
        C
              DO I = 1, NDAF
                 CALL DAFOPR ( DAFNAM(I), HAN(I) )
              END DO

        C
        C     Obtain the start and end addresses of the
        C     data in each DAF.  To do this, we'll need to
        C     obtain and unpack the array summaries.
        C
        C     If all went well, the addresses should be the
        C     same for each DAF.  We'll assume that the initial
        C     and final addresses in the first DAF are correct
        C     for all three.
        C
              CALL DAFBFS ( HAN(1) )
              CALL DAFFNA ( FOUND  )
              CALL DAFGS  ( SUMMRY )
              CALL DAFUS  ( SUMMRY, ND, NI, DC, IC )

              IA      =  IC( NI-1 )
              FA      =  IC( NI   )
              LENGTH  =  FA - IA + 1

        C
        C     Now read numbers from the DAFs and build up
        C     lines of text.  Print these lines out.
        C
              DO I = 0,  LENGTH - 1

                 LINE = ' '

                 DO J = 1, NDAF

                    CALL DAFRDA ( HAN(J), IA+I, IA+I, NUMDP )

        C
        C           Convert the double precision number to a
        C           character string, and append it to the current
        C           line.
        C
                    CALL DPSTR  ( NUMDP,  SIG,        NUMCH )
                    CALL SUFFIX ( NUMCH,  3,          LINE  )

                 END DO

                 WRITE(*,*) LINE

              END DO

        C
        C     Close the DAFs.
        C
              DO I = 1, NDAF
                 CALL DAFCLS( HAN(I) )
              END DO

              END


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


             1.100000000E+01    1.200000000E+01    1.300000000E+01
             2.100000000E+01    2.200000000E+01    2.300000000E+01
             3.100000000E+01    3.200000000E+01    3.300000000E+01
             4.100000000E+01    4.200000000E+01    4.300000000E+01
             5.100000000E+01    5.200000000E+01    5.200000000E+01
             6.100000000E+01    6.200000000E+01    6.300000000E+01
             7.100000000E+01    7.200000000E+01    7.300000000E+01
             8.100000000E+01    8.200000000E+01    8.300000000E+01
             9.100000000E+01    9.200000000E+01    9.300000000E+01


        Note that after run completion, three new DAF files exist in
        the output directory.

Restrictions

     None.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     K.R. Gehringer     (JPL)
     H.A. Neilan        (JPL)
     W.L. Taber         (JPL)
     F.S. Turner        (JPL)
     I.M. Underwood     (JPL)

Version

    SPICELIB Version 3.1.0, 13-AUG-2021 (JDR)

        Added IMPLICIT NONE statement.

        Edited the header of DAFANA and all entry points to comply with
        NAIF standard. Added complete code examples to DAFANA $Examples
        section based on the existing fragments.

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

        Updated the entry points of DAFANA to enable its
        internal state table size, TBSIZE, to be smaller
        than the file table maintained by DAFAH: FTSIZE.

    SPICELIB Version 2.1.0, 11-JUL-1995 (KRG)

        Updated to remove potential compiler warnings from the
        truncation of double precision numbers to integers.

        Also changed was a numeric constant from 1.D0 to the
        equivalent, but more aesthetically pleasing 1.0D0.

    SPICELIB Version 2.0.1, 10-MAR-1992 (WLT)

        Comment section for permuted index source lines was added
        following the header.

    SPICELIB Version 2.0.0, 04-SEP-1991 (NJB) (WLT)

        Updated to support simultaneous writes to multiple DAFs.
        The $Examples section of this routine now illustrates
        usage of the routine DAFCAD.

    SPICELIB Version 1.0.1, 22-MAR-1990 (HAN)

        Literature references added to the header.

    SPICELIB Version 1.0.0, 31-JAN-1990 (IMU)
Fri Dec 31 18:36:06 2021