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
spkgps

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

     SPKGPS ( S/P Kernel, geometric position )

     SUBROUTINE SPKGPS ( TARG, ET, REF, OBS, POS, LT )

Abstract

     Compute the geometric position of a target body relative to an
     observing body.

Required_Reading

     SPK

Keywords

     EPHEMERIS

Declarations

     IMPLICIT NONE

     INCLUDE               'ninert.inc'
     INCLUDE               'zzctr.inc'

     INTEGER               TARG
     DOUBLE PRECISION      ET
     CHARACTER*(*)         REF
     INTEGER               OBS
     DOUBLE PRECISION      POS ( 3 )
     DOUBLE PRECISION      LT

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     TARG       I   Target body.
     ET         I   Target epoch.
     REF        I   Target reference frame.
     OBS        I   Observing body.
     POS        O   Position of target.
     LT         O   Light time.

Detailed_Input

     TARG     is the standard NAIF ID code for a target body.

     ET       is the epoch (ephemeris time) at which the position
              of the target body is to be computed.

     REF      is the name of the reference frame to
              which the vectors returned by the routine should
              be rotated. This may be any frame supported by
              the SPICELIB subroutine REFCHG.

     OBS      is the standard NAIF ID code for an observing body.

Detailed_Output

     POS      is a 3-dimensional vector that contains the position of
              the target body, relative to the observing body. This
              vector is rotated into the specified reference frame.
              Units are always km.

     LT       is the one-way light time from the observing body
              to the geometric position of the target body at the
              specified epoch.

Parameters

     None.

Exceptions

     1)  If insufficient ephemeris data has been loaded to compute
         the necessary positions, the error SPICE(SPKINSUFFDATA) is
         signaled.

Files

     See $Restrictions.

Particulars

     SPKGPS computes the geometric position, T(t), of the target
     body and the geometric position, O(t), of the observing body
     relative to the first common center of motion. Subtracting
     O(t) from T(t) gives the geometric position of the target
     body relative to the observer.


        CENTER ----- O(t)
            |      /
            |     /
            |    /
            |   /  T(t) - O(t)
            |  /
           T(t)


     The one-way light time, tau, is given by


               | T(t) - O(t) |
        tau = -----------------
                      c


     For example, if the observing body is -94, the Mars Observer
     spacecraft, and the target body is 401, Phobos, then the
     first common center is probably 4, the Mars Barycenter.
     O(t) is the position of -94 relative to 4 and T(t) is the
     position of 401 relative to 4.

     The center could also be the Solar System Barycenter, body 0.
     For example, if the observer is 399, Earth, and the target
     is 299, Venus, then O(t) would be the position of 399 relative
     to 0 and T(t) would be the position of 299 relative to 0.

     Ephemeris data from more than one segment may be required
     to determine the positions of the target body and observer
     relative to a common center. SPKGPS reads as many segments
     as necessary, from as many files as necessary, using files
     that have been loaded by previous calls to SPKLEF (load
     ephemeris file).

     SPKGPS is similar to SPKGEO but returns geometric positions
     only.

Examples

     The following code example computes the geometric
     position of the moon with respect to the earth and
     then prints the distance of the moon from the
     the earth at a number of epochs.

     Assume the SPK file SAMPLE.BSP contains ephemeris data
     for the moon relative to earth over the time interval
     from BEGIN to END.

            INTEGER               EARTH
            PARAMETER           ( EARTH = 399 )

            INTEGER               MOON
            PARAMETER           ( MOON  = 301 )

            INTEGER               N
            PARAMETER           ( N     = 100 )

            INTEGER               I
            CHARACTER*(20)        UTC
            DOUBLE PRECISION      BEGIN
            DOUBLE PRECISION      DELTA
            DOUBLE PRECISION      END
            DOUBLE PRECISION      ET
            DOUBLE PRECISION      POS ( 3 )
            DOUBLE PRECISION      LT

            DOUBLE PRECISION      VNORM

     C
     C      Load the binary SPK ephemeris file.
     C
            CALL FURNSH ( 'SAMPLE.BSP' )

            .
            .
            .

     C
     C      Divide the interval of coverage [BEGIN,END] into
     C      N steps. At each step, compute the position, and
     C      print out the epoch in UTC time and position norm.
     C
            DELTA = ( END - BEGIN ) / N

            DO I = 0, N

               ET = BEGIN + I*DELTA

               CALL SPKGPS ( MOON, ET, 'J2000', EARTH, POS, LT )

               CALL ET2UTC ( ET, 'C', 0, UTC )

               WRITE (*,*) UTC, VNORM ( POS )

            END DO

Restrictions

     1)  The ephemeris files to be used by SPKGPS must be loaded
         by SPKLEF before SPKGPS is called.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     B.V. Semenov       (JPL)
     W.L. Taber         (JPL)

Version

    SPICELIB Version 2.1.0, 09-OCT-2021 (JDR) (NJB)

        Bug fix: added calls to FAILED after calls to SPKPVN.
        Previously only one call to SPKPVN was followed by a FAILED
        call. Moved some FAILED checks so they will be hit whether
        or not SPKSFS finds a segment.

        Edited the header to comply with NAIF standard. Removed
        unnecessary $Revisions section.

    SPICELIB Version 2.0.0, 08-JAN-2014 (BVS)

        Updated to save the input frame name and POOL state counter
        and to do frame name-ID conversion only if the counter has
        changed.

        Updated to map the input frame name to its ID by first calling
        ZZNAMFRM, and then calling IRFNUM. The side effect of this
        change is that now the frame with the fixed name 'DEFAULT'
        that can be associated with any code via CHGIRF's entry point
        IRFDEF will be fully masked by a frame with identical name
        defined via a text kernel. Previously the CHGIRF's 'DEFAULT'
        frame masked the text kernel frame with the same name.

        Replaced SPKLEF with FURNSH and fixed errors in $Examples.

    SPICELIB Version 1.2.0, 05-NOV-2005 (NJB)

        Updated to remove non-standard use of duplicate arguments
        in VADD calls.

    SPICELIB Version 1.1.0, 05-JAN-2005 (NJB)

        Tests of routine FAILED() were added.

    SPICELIB Version 1.0.0, 09-JUL-1998 (WLT)
Fri Dec 31 18:36:52 2021