Index Page
ckcov
A  B  C  D  E  F  G  H  I  J  K  L  M  N  O  P  Q  R  S  T  U  V  W  X 

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

      CKCOV ( CK coverage )
 
      SUBROUTINE CKCOV ( CK, IDCODE, NEEDAV, LEVEL, TOL, TIMSYS, COVER )
 

Abstract

     Find the coverage window for a specified object in a specified CK
     file.

Required_Reading

     CELLS
     DAF
     CK
     TIME
     WINDOWS

Keywords

     POINTING
     TIME
     UTILITY

Declarations


      INTEGER               LBCELL
      PARAMETER           ( LBCELL = -5 )

      CHARACTER*(*)         CK
      INTEGER               IDCODE
      LOGICAL               NEEDAV
      CHARACTER*(*)         LEVEL
      DOUBLE PRECISION      TOL
      CHARACTER*(*)         TIMSYS
      DOUBLE PRECISION      COVER ( LBCELL : * )
 

Brief_I/O

     Variable  I/O  Description
     --------  ---  --------------------------------------------------
     CK         I   Name of CK file.
     IDCODE     I   ID code of object.
     NEEDAV     I   Flag indicating whether angular velocity is needed.
     LEVEL      I   Coverage level:  'SEGMENT' OR 'INTERVAL'.
     TOL        I   Tolerance in ticks.
     TIMSYS     I   Time system used to represent coverage.
     COVER     I/O  Window giving coverage for IDCODE.

Detailed_Input

     CK             is the name of a C-kernel.
     
     IDCODE         is the integer ID code of an object, normally
                    a spacecraft structure or instrument, for which
                    pointing data are expected to exist in the
                    specified CK file.

     NEEDAV         is a logical variable indicating whether only
                    segments having angular velocity are to be
                    considered when determining coverage.  When
                    NEEDAV is .TRUE., segments without angular
                    velocity don't contribute to the coverage 
                    window; when NEEDAV is .FALSE., all segments for 
                    IDCODE may contribute to the coverage window.


     LEVEL          is the level (granularity) at which the coverage
                    is examined.  Allowed values and corresponding
                    meanings are:

                       'SEGMENT'    The output coverage window
                                    contains intervals defined by the
                                    start and stop times of segments
                                    for the object designated by
                                    IDCODE.

                       'INTERVAL'   The output coverage window
                                    contains interpolation intervals
                                    of segments for the object
                                    designated by IDCODE.  For type 1
                                    segments, which don't have
                                    interpolation intervals, each
                                    epoch associated with a pointing
                                    instance is treated as a singleton
                                    interval; these intervals are
                                    added to the coverage window.

                                    All interpolation intervals are
                                    considered to lie within the
                                    segment bounds for the purpose of
                                    this summary:  if an interpolation
                                    interval extends beyond the
                                    segment coverage interval, only
                                    its intersection with the segment
                                    coverage interval is considered to
                                    contribute to the total coverage.
                                                                   

     TOL            is a tolerance value expressed in ticks of the
                    spacecraft clock associated with IDCODE.  Before
                    each interval is inserted into the coverage
                    window, the interval is intersected with the
                    segment coverage interval, then if the
                    intersection is non-empty, it is expanded by TOL:
                    the left endpoint of the intersection interval is
                    reduced by TOL and the right endpoint is increased
                    by TOL. Adjusted interval endpoints, when
                    expressed as encoded SCLK, never are less than
                    zero ticks.  Any intervals that overlap as a
                    result of the expansion are merged.

                    The coverage window returned when TOL > 0
                    indicates the coverage provided by the file to the
                    CK readers CKGPAV and CKGP when that value of TOL
                    is passed to them as an input.

                
     TIMSYS         is a string indicating the time system used
                    in the output coverage window.  TIMSYS may 
                    have the values:
 
                        'SCLK'    Elements of COVER are expressed in
                                  encoded SCLK ("ticks"), where the
                                  clock is associated with the object
                                  designated by IDCODE.

                        'TDB'     Elements of COVER are expressed as
                                  seconds past J2000 TDB.


     COVER          is an initialized SPICELIB window data structure.
                    COVER optionally may contain coverage data on
                    input; on output, the data already present in
                    COVER will be combined with coverage found for the
                    object designated by IDCODE in the file CK.

                    If COVER contains no data on input, its size and
                    cardinality still must be initialized.

Detailed_Output

     COVER          is a SPICELIB window data structure which
                    represents the merged coverage for IDCODE. When
                    the coverage level is 'INTERVAL', this is the set
                    of time intervals for which data for IDCODE are
                    present in the file CK, merged with the set of
                    time intervals present in COVER on input.  The
                    merged coverage is represented as the union of one
                    or more disjoint time intervals.  The window COVER
                    contains the pairs of endpoints of these
                    intervals.

                    When the coverage level is 'SEGMENT', COVER is
                    computed in a manner similar to that described
                    above, but the coverage intervals used in the
                    computation are those of segments rather than
                    interpolation intervals within segments. 

                    When TOL is > 0, the intervals comprising the
                    coverage window for IDCODE are expanded by TOL and
                    any intervals overlapping as a result are merged.
                    The resulting window is returned in COVER.  The
                    expanded window in no case extends beyond the
                    segment bounds in either direction by more than
                    TOL.

                    The interval endpoints contained in COVER are
                    encoded spacecraft clock times if TIMSYS is
                    'SCLK'; otherwise the times are converted from
                    encoded spacecraft clock to seconds past J2000
                    TDB.

                    See the Examples section below for a complete
                    example program showing how to retrieve the
                    endpoints from COVER.
                                      

Parameters

     None.

Exceptions

     1)  If the input file has transfer format, the error 
         SPICE(INVALIDFORMAT) is signaled.

     2)  If the input file is not a transfer file but has architecture
         other than DAF, the the error SPICE(BADARCHTYPE) is signaled.

     3)  If the input file is a binary DAF file of type other than
         CK, the error SPICE(BADFILETYPE) is signaled.

     4)  If the CK file cannot be opened or read, the error will
         be diagnosed by routines called by this routine. The output
         window will not be modified.

     5)  If the size of the output WINDOW argument COVER is
         insufficient to contain the actual number of intervals in the
         coverage window for IDCODE, the error will be diagnosed by
         routines called by this routine.  

     6)  If TOL is negative, the error SPICE(VALUEOUTOFRANGE) is
         signaled.

     7)  If LEVEL is not recognized, the error SPICE(INVALIDOPTION)
         is signaled.

     8)  If TIMSYS is not recognized, the error SPICE(NOTSUPPORTED)
         is signaled.

     9)  If a time conversion error occurs, the error will be 
         diagnosed by a routine in the call tree of this routine.

     10) If the output time system is TDB, the CK subsystem must be
         able to map IDCODE to the ID code of the associated
         spacecraft clock.  If this mapping cannot be performed, the
         error will be diagnosed by a routine in the call tree of this
         routine.

Files

     This routine reads a C-kernel.

     If the output time system is 'TDB', then a leapseconds kernel
     and an SCLK kernel for the spacecraft clock associated with
     IDCODE must be loaded before this routine is called.

     If the ID code of the clock associated with IDCODE is not 
     equal to 

        IDCODE / 1000

     then the kernel variable 

        CK_<IDCODE>_SCLK
   
     must be present in the kernel pool to identify the clock
     associated with IDCODE.  This variable must contain the ID code
     to be used for conversion between SCLK and TDB. Normally this
     variable is provided in a text kernel loaded via FURNSH.

Particulars

     This routine provides an API via which applications can determine
     the coverage a specified CK file provides for a specified
     object.

Examples

     1)  Display the interval-level coverage for each object in a
         specified CK file. Use tolerance of zero ticks. Do not
         request angular velocity. Express the results in the TDB time
         system.

         Find the set of objects in the file. Loop over the contents
         of the ID code set:  find the coverage for each item in the
         set and display the coverage.


              PROGRAM CKCVR
              IMPLICIT NONE

        C
        C     SPICELIB functions
        C
              INTEGER               WNCARD
              INTEGER               CARDI
        C
        C     Local parameters
        C
        C
        C     Declare the coverage window.  Make enough room
        C     for MAXIV intervals.
        C
              INTEGER               FILSIZ
              PARAMETER           ( FILSIZ = 255 )

              INTEGER               LBCELL
              PARAMETER           ( LBCELL = -5 )

              INTEGER               MAXIV
              PARAMETER           ( MAXIV  = 100000 )

              INTEGER               WINSIZ
              PARAMETER           ( WINSIZ = 2 * MAXIV )

              INTEGER               TIMLEN
              PARAMETER           ( TIMLEN = 50 )

              INTEGER               MAXOBJ
              PARAMETER           ( MAXOBJ = 1000 )

        C
        C     Local variables
        C
              CHARACTER*(FILSIZ)    CK
              CHARACTER*(FILSIZ)    LSK
              CHARACTER*(FILSIZ)    SCLK
              CHARACTER*(TIMLEN)    TIMSTR

              DOUBLE PRECISION      B
              DOUBLE PRECISION      COVER ( LBCELL : WINSIZ )
              DOUBLE PRECISION      E

              INTEGER               I
              INTEGER               IDS   ( LBCELL : MAXOBJ )
              INTEGER               J
              INTEGER               NIV

        C
        C     Load a leapseconds kernel and SCLK kernel for output
        C     time conversion.  Note that we assume a single spacecraft
        C     clock is associated with all of the objects in the CK.
        C
              CALL PROMPT ( 'Name of leapseconds kernel > ', LSK  )
              CALL FURNSH ( LSK )

              CALL PROMPT ( 'Name of SCLK kernel        > ', SCLK )
              CALL FURNSH ( SCLK )

        C
        C     Get name of CK file.
        C
              CALL PROMPT ( 'Name of CK file            > ', CK )

        C
        C     Initialize the set IDS.
        C
              CALL SSIZEI ( MAXOBJ, IDS )

        C
        C     Initialize the window COVER.
        C
              CALL SSIZED ( WINSIZ, COVER )

        C
        C     Find the set of objects in the CK file.
        C
              CALL CKOBJ ( CK, IDS )

        C
        C     We want to display the coverage for each object.  Loop
        C     over the contents of the ID code set, find the coverage
        C     for each item in the set, and display the coverage.
        C
              DO I = 1, CARDI( IDS )
        C
        C        Find the coverage window for the current 
        C        object. Empty the coverage window each time 
        C        so we don't include data for the previous object.
        C
                 CALL SCARDD ( 0,   COVER )
                 CALL CKCOV  ( CK,          IDS(I),  .FALSE.,
             .                 'INTERVAL',  0.D0,    'TDB',    COVER )

        C
        C        Get the number of intervals in the coverage
        C        window.
        C
                 NIV = WNCARD( COVER )

        C
        C        Display a simple banner.
        C
                 WRITE (*,*) '========================================'
                 WRITE (*,*) 'Coverage for object ', IDS(I)

        C
        C        Convert the coverage interval start and stop
        C        times to TDB calendar strings.
        C
                 DO J = 1, NIV
        C
        C           Get the endpoints of the Jth interval.
        C
                    CALL WNFETD ( COVER, J, B, E )
        C
        C           Convert the endpoints to TDB calendar
        C           format time strings and display them.
        C
                    CALL TIMOUT ( B,
             .                    'YYYY MON DD HR:MN:SC.###### ' //
             .                    '(TDB) ::TDB',
             .                    TIMSTR                           )
                    WRITE (*,*) ' '
                    WRITE (*,*) 'Interval: ', J
                    WRITE (*,*) 'Start:    ', TIMSTR

                    CALL TIMOUT ( E,
             .                    'YYYY MON DD HR:MN:SC.###### ' //
             .                    '(TDB) ::TDB',
             .                    TIMSTR                          )
                    WRITE (*,*) 'Stop:     ', TIMSTR
                    WRITE (*,*) ' '

                 END DO

                 WRITE (*,*) '========================================'

              END DO

              END


     2)  Find the segment-level coverage for the object designated by
         IDCODE provided by the set of CK files loaded via a
         metakernel. (The metakernel must also specify leapseconds and
         SCLK kernels.)  Use tolerance of zero ticks. Do not request
         angular velocity. Express the results in the TDB time system.

              PROGRAM CKMET
              IMPLICIT NONE
        C
        C     SPICELIB functions
        C
              INTEGER               WNCARD

        C
        C     Local parameters
        C
              INTEGER               LBCELL
              PARAMETER           ( LBCELL = -5 )

              INTEGER               FILSIZ
              PARAMETER           ( FILSIZ = 255 )

              INTEGER               LNSIZE
              PARAMETER           ( LNSIZE = 80 )

              INTEGER               MAXCOV
              PARAMETER           ( MAXCOV = 100000 )

              INTEGER               TIMLEN
              PARAMETER           ( TIMLEN = 50 )

        C
        C     Local variables
        C
              CHARACTER*(FILSIZ)    FILE
              CHARACTER*(LNSIZE)    IDCH
              CHARACTER*(FILSIZ)    META
              CHARACTER*(FILSIZ)    SOURCE
              CHARACTER*(TIMLEN)    TIMSTR
              CHARACTER*(LNSIZE)    TYPE

              DOUBLE PRECISION      B
              DOUBLE PRECISION      COVER  ( LBCELL : 2*MAXCOV )
              DOUBLE PRECISION      E

              INTEGER               COUNT
              INTEGER               HANDLE
              INTEGER               I
              INTEGER               IDCODE
              INTEGER               NIV

              LOGICAL               FOUND

        C
        C     Prompt for the metakernel name; load the metakernel.
        C     The metakernel lists the CK files whose coverage
        C     for IDCODE we'd like to determine.  The metakernel
        C     must also specify a leapseconds kernel and an SCLK
        C     kernel for the clock associated with IDCODE.
        C
              CALL PROMPT ( 'Enter name of metakernel > ', META )

              CALL FURNSH ( META )

        C
        C     Get the ID code of interest.
        C
              CALL PROMPT ( 'Enter ID code            > ', IDCH )

              CALL PRSINT ( IDCH,  IDCODE )

        C
        C     Initialize the coverage window.
        C
              CALL SSIZED ( MAXCOV, COVER )

        C
        C     Find out how many kernels are loaded.  Loop over the
        C     kernels:  for each loaded CK file, add its coverage
        C     for IDCODE, if any, to the coverage window.
        C
              CALL KTOTAL ( 'CK', COUNT )

              DO I = 1, COUNT

                 CALL KDATA ( I,       'CK',    FILE,  TYPE,
             .                SOURCE,  HANDLE,  FOUND       )

                 CALL CKCOV  (  FILE,       IDCODE,  .FALSE.,
             .                  'SEGMENT',  0.0,     'TDB',    COVER )

              END DO

        C
        C     Display results.
        C
        C     Get the number of intervals in the coverage
        C     window.
        C
              NIV = WNCARD( COVER )

        C
        C     Display a simple banner.
        C
              WRITE (*,*) ' '
              WRITE (*,*) 'Coverage for object ', IDCODE

        C
        C     Convert the coverage interval start and stop
        C     times to TDB calendar strings.
        C
              DO I = 1, NIV
        C
        C        Get the endpoints of the Ith interval.
        C
                 CALL WNFETD ( COVER, I, B, E )
        C
        C        Convert the endpoints to TDB calendar
        C        format time strings and display them.
        C
                 CALL TIMOUT ( B,
             .                 'YYYY MON DD HR:MN:SC.###### ' //
             .                 '(TDB) ::TDB',
             .                 TIMSTR                           )
                 WRITE (*,*) ' '
                 WRITE (*,*) 'Interval: ', I
                 WRITE (*,*) 'Start:    ', TIMSTR

                 CALL TIMOUT ( E,
             .                 'YYYY MON DD HR:MN:SC.###### ' //
             .                 '(TDB) ::TDB',
             .                 TIMSTR                           )
                 WRITE (*,*) 'Stop:     ', TIMSTR
                 WRITE (*,*) ' '

              END DO

              END

Restrictions

     1) When this routine is used to accumulate coverage for IDCODE
        provided by multiple CK files, the inputs NEEDAV, LEVEL, TOL,
        and TIMSYS  must have the same values for all files in order
        for the result to be meaningful. 

Literature_References

     None.

Author_and_Institution

     N.J. Bachman   (JPL)

Version

    SPICELIB Version 1.0.1, 30-NOV-2007 (NJB)

        Corrected bug in first program in header Examples section:
        program now empties the coverage window prior to collecting
        data for the current object. Updated examples to use WNCARD
        rather than CARDD.

    SPICELIB Version 1.0.0, 07-JAN-2005 (NJB)
Tue Mar  4 09:35:52 2008