cda_pointing.f

      PROGRAM CDA_POINTING

C
C     This example program computes the CASSINI CDA pointing direction
C     at equally spaced points during a specified time interval. It is
C     a command line program requiring the following arguments:
C
C        -  the name of a meta-kernel listing SPICE kernels needed to
C           compute CDA geometry during the specified time span
C
C        -  a begin time in YYYY-MM-DDTHR:MN:SC.### format
C
C        -  an end time in YYYY-MM-DDTHR:MN:SC.### format
C
C        -  a step size in seconds
C
C        -  the name of the reference frame in which the direction
C           of the boresight should be computed (J2000, ECLIPJ2000,
C           etc).
C
C        -  the output file name.
C
C     The output file is a text file in which each line contains
C     comma-delimited UTC time in YYYY-MM-DDTHR:MN:SC.### format and
C     CDA boresight pointing direction expressed as RA and DEC in
C     degrees. If the SPICE data provided to the program are not
C     sufficient to compute CASSINI spacecraft or CDA orientation for
C     any of the points, the corresponding record of the output file
C     will contain "CASSINI pointing not found", "CDA pointing not
C     found", or "CASSINI and CDA pointing not found" instead of RA and
C     DEC. The "pointing not found" records can be filtered out of the
C     file at a later time using "grep -v 'not found'" command.
C
C     Contact Boris.Semenov@jpl.nasa.gov if you have any questions
C     about this program.
C
C     December 13, 2006
C
      IMPLICIT NONE
      
C
C     Parameters.
C
C     NAIF ID for CASSINI s/c (built into SPICE, see naif_ids.req).
C     This parameter is used in the SCE2E call.
C
      INTEGER               CASID
      PARAMETER           ( CASID  = -82 )

C
C     NAIF ID for CDA (defined in the CDA IK file, cas_cda_v01.ti).
C     This parameter is used in the GETFOV call.
C
      INTEGER               CDAID
      PARAMETER           ( CDAID  = -82790 )

C
C     CK IDs and frame pairs for the data provided by the CASSINI s/c
C     and CDA CK files (to find these IDs, run CKBRIEF utility
C     (ckbrief.ug) to summarize a CASSINI CK and the CDA CK or examine
C     the frame layout in the CASSINI FK file, cas_v39.tf). These
C     parameters are used in the CKGP calls.
C
      INTEGER               CASCID
      PARAMETER           ( CASCID = -82000 )

      CHARACTER*(*)         CASCFR
      PARAMETER           ( CASCFR = 'J2000' )

      INTEGER               CDACID
      PARAMETER           ( CDACID  = -82790 )

      CHARACTER*(*)         CDACFR
      PARAMETER           ( CDACFR = 'CASSINI_CDA_BASE' )

C
C     Miscellaneous string sizes.
C
      INTEGER               LINLEN
      PARAMETER           ( LINLEN = 1024 )

      INTEGER               WRDLEN
      PARAMETER           ( WRDLEN = 32 )


C
C     Variable declarations in the order they appear in the calls made
C     by the program.
C
      CHARACTER*(LINLEN)    LINE
      
      INTEGER               I

      CHARACTER*(LINLEN)    MKFILE
      CHARACTER*(WRDLEN)    BEGUTC
      CHARACTER*(WRDLEN)    ENDUTC
      CHARACTER*(WRDLEN)    STEPCH
      CHARACTER*(WRDLEN)    FRAME
      CHARACTER*(LINLEN)    OUTFIL

      DOUBLE PRECISION      BEGET
      DOUBLE PRECISION      ENDET
      DOUBLE PRECISION      STEP

      CHARACTER*(WRDLEN)    SHAPE
      CHARACTER*(WRDLEN)    IFRAME
      DOUBLE PRECISION      BSIGHT ( 3 )
      INTEGER               N
      DOUBLE PRECISION      BOUNDS ( 3, 1 )

      INTEGER               FUNIT

      DOUBLE PRECISION      ET

      DOUBLE PRECISION      SCLKDP

      DOUBLE PRECISION      MAT    ( 3, 3 )
      DOUBLE PRECISION      CLKOUT
      LOGICAL               CASFND

      LOGICAL               CDAFND

      DOUBLE PRECISION      BOUTPT ( 3 )

      DOUBLE PRECISION      R
      DOUBLE PRECISION      RA
      DOUBLE PRECISION      DEC

      CHARACTER*(WRDLEN)    HWORD

C
C     SPICELIB function declarations.
C
      DOUBLE PRECISION      DPR
      INTEGER               WDCNT

C
C     Get command line. Display usage if it does not contain the
C     expected number of arguments.
C
      CALL GETCML( LINE )
      IF ( WDCNT(LINE) .NE. 6 ) THEN
         WRITE (*,*) ' '
         WRITE (*,*) 'Usage: '
         WRITE (*,*) ' '
         WRITE (*,*) '% cda_pointing furnsh begin end step frame file'
         WRITE (*,*) ' '
         STOP
      END IF

C
C     Extract command arguments.
C
      CALL NTHWD ( LINE, 1, MKFILE, I )
      CALL NTHWD ( LINE, 2, BEGUTC, I )
      CALL NTHWD ( LINE, 3, ENDUTC, I )
      CALL NTHWD ( LINE, 4, STEPCH, I )
      CALL NTHWD ( LINE, 5, FRAME,  I )
      CALL NTHWD ( LINE, 6, OUTFIL, I )

C
C     Load kernels listed in the meta-kernel.
C      
      CALL FURNSH ( MKFILE )

C
C     Convert begin and end UTC strings (variables BEGUTC and ENDUTC)
C     to ephemeris seconds past J2000 (variables BEGET and ENDET).
C
      CALL STR2ET ( BEGUTC, BEGET )
      CALL STR2ET ( ENDUTC, ENDET )

C
C     Convert the string containing step (STEPCH) in seconds to a DP
C     number (STEP).
C
      CALL PRSDP  ( STEPCH, STEP )

C
C     Get CASSINI CDA boresight direction (BSIGHT) and the frame with
C     respect to which it is defined (IFRAME) from the instrument FOV
C     definition provided in the IK file (cas_cda_v01.ti).
C
      CALL GETFOV ( CDAID, 1, SHAPE, IFRAME, BSIGHT, N, BOUNDS )

C
C     Open output file and save its logical unit (FUNIT).
C
      CALL TXTOPN ( OUTFIL, FUNIT )

C
C     Step from begin time to specified end time with specified
C     step.
C
      ET = BEGET

      DO WHILE ( ET .LE. ENDET ) 

C
C        Convert current ephemeris time to UTC for output. Append a
C        comma. The time with comma will be the head of the output
C        line.
C
         CALL TIMOUT ( ET, 'YYYY-MM-DDTHR:MN:SC.### ::RND', LINE )
         CALL SUFFIX ( ',',  0, LINE )

C
C        Convert ephemeris time to encoded on-board clock time
C        (SCLKDP). It is need to call CKGP routines to check whether
C        attitude data for the spacecraft and CDA is available in the
C        loaded CK files.
C
         CALL SCE2T ( CASID, ET, SCLKDP )

C
C        Call CKGP with the ID and FRAME matching those in the CASSINI
C        s/c CK files to check if spacecraft attitude for this time is
C        available in the loaded CK files. CASFND will be set to .TRUE.
C        if it is.
C
         CALL CKGP ( CASCID, SCLKDP, 0.D0, CASCFR, MAT, CLKOUT, CASFND)

C
C        Call CKGP with the ID and FRAME matching those in the CDA CK
C        file to check if CDA attitude for this time is available in
C        the loaded CK file. CDAFND will be set to .TRUE. if it is.
C
         CALL CKGP ( CDACID, SCLKDP, 0.D0, CDACFR, MAT, CLKOUT, CDAFND)
         
C
C        If attitude is not available, append the message indicating
C        that to the output line.
C
         IF      ( ( .NOT. CASFND ) .AND. ( .NOT. CDAFND ) ) THEN

            CALL SUFFIX( 'CASSINI and CDA pointing not found', 1, LINE )

         ELSE IF (   .NOT. CASFND   ) THEN         

            CALL SUFFIX( 'CASSINI pointing not found', 1, LINE )

         ELSE IF (   .NOT. CDAFND   ) THEN         

            CALL SUFFIX( 'CDA pointing not found', 1, LINE )

         ELSE

C
C           Attitude data is available for the spacecraft and for CDA.
C           We can proceed to compute boresight direction in the
C           specified output reference frame.
C           
C
C           First, compute matrix rotating vectors from the CDA frame
C           to the output frame.
C
            CALL PXFORM( IFRAME, FRAME, ET, MAT )

C
C           Multiply boresight vector defined in the instrument frame
C           by this matrix to get boresight direction in the output
C           frame.
C
            CALL MXV   ( MAT, BSIGHT, BOUTPT )

C
C           Convert boresight direction to RA/DEC.
C
            CALL RECRAD( BOUTPT, R, RA, DEC )

C
C           Append convert RA and DEC to degrees (by multiplying by
C           DPR), then to strings and append them to the output line.
C           
            CALL DPFMT ( RA*DPR(),  'xxxx.xxx', HWORD )
            CALL SUFFIX( HWORD, 1, LINE )
            CALL SUFFIX( ',', 0, LINE )

            CALL DPFMT ( DEC*DPR(), 'xxxx.xxx', HWORD )
            CALL SUFFIX( HWORD, 1, LINE )

         END IF

C
C        Write output line to the file.
C
         CALL WRITLN ( LINE, FUNIT )

C
C        Increment time.
C
         ET = ET + STEP

      END DO

C
C     Close output file.
C
      CLOSE ( FUNIT ) 

C
C     All done.
C

      END