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
unitim

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

     UNITIM ( Uniform time scale transformation )

     DOUBLE PRECISION FUNCTION UNITIM ( EPOCH, INSYS, OUTSYS )

Abstract

     Transform time from one uniform scale to another. The uniform
     time scales are TAI, GPS, TT, TDT, TDB, ET, JED, JDTDB, JDTDT.

Required_Reading

     TIME

Keywords

     CONVERSION
     TIME
     UTILITY

Declarations

     IMPLICIT NONE

     INCLUDE               'zzctr.inc'

     DOUBLE PRECISION      EPOCH
     CHARACTER*(*)         INSYS
     CHARACTER*(*)         OUTSYS

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     EPOCH      I   An epoch.
     INSYS      I   The time scale associated with the input EPOCH.
     OUTSYS     I   The time scale associated with the function value.

     The function returns the d.p. in OUTSYS that is equivalent to the
     EPOCH on the INSYS time scale.

Detailed_Input

     EPOCH    is an epoch relative to the INSYS time scale.

     INSYS    is a time scale. Acceptable values are:

                 'TAI'     International Atomic Time.
                 'TDB'     Barycentric Dynamical Time.
                 'TDT'     Terrestrial Dynamical Time.
                 'TT'      Terrestrial Time, identical to TDT.
                 'ET'      Ephemeris time (in the SPICE system, this is
                           equivalent to TDB).
                 'JDTDB'   Julian Date relative to TDB.
                 'JDTDT'   Julian Date relative to TDT.
                 'JED'     Julian Ephemeris date (in the SPICE system
                           this is equivalent to JDTDB).
                 'GPS'     Global Positioning System Time.

              The routine is not sensitive to the case of the
              characters in INSYS; 'tai' 'Tai' and 'TAI' are all
              equivalent from the point of view of this routine.

     OUTSYS   is the time scale to which EPOCH should be converted.
              Acceptable values are the same as for INSYS. The
              routine is not sensitive to the case of OUTSYS.

Detailed_Output

     The function returns the time in the system specified by OUTSYS
     that is equivalent to the EPOCH in the INSYS time scale.

Parameters

     None.

Exceptions

     1)  The kernel pool must contain the variables:

            'DELTET/DELTA_T_A'
            'DELTET/K'
            'DELTET/EB'
            'DELTET/M'

         If these are not present, the error SPICE(MISSINGTIMEINFO) is
         signaled. (These variables are typically inserted into the
         kernel pool by loading a leapseconds kernel with the SPICE
         routine FURNSH.)

     2)  If the names of either the input or output time types are
         unrecognized, the error SPICE(BADTIMETYPE) is signaled.

Files

     None.

Particulars

     We use the term uniform time scale to refer to those
     representations of time that are numeric (each epoch is
     represented by a number) and additive. A numeric time system is
     additive if given the representations, E1 and E2, of any pair of
     successive epochs, the time elapsed between the epochs is given by
     E2 - E1.

     Given an epoch in one of the uniform time scales specified by
     INSYS, the function returns the equivalent representation in the
     scale specified by OUTSYS. A list of the recognized uniform time
     scales is given in the detailed input for INSYS.

Examples

     To convert an epoch with respect to the International Atomic
     Time (TAI) scale to ET (Barycentric Dynamical Time), make the
     following assignment.

           ET = UNITIM ( TAI, 'TAI', 'ET' )

Restrictions

     1)  The appropriate variable must be loaded into the SPICE kernel
         pool (normally by loading a leapseconds kernel with FURNSH)
         prior to calling this routine.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     H.A. Neilan        (JPL)
     B.V. Semenov       (JPL)
     W.L. Taber         (JPL)
     E.D. Wright        (JPL)

Version

    SPICELIB Version 1.5.0, 05-SEP-2020 (EDW) (JDR)

        Added time system name 'TT' (Terrestrial Time) as alternate
        assignment of 'TDT' (Terrestrial Dynamical Time).

        Included GPS time system mapping.

        Edited the header to comply with NAIF standard.

        Removed references to FURNSH, CLPOOL, KCLEAR, UNLOAD, and
        Required Reading documents and tutorials from the "variables
        not present" long error message. 

    SPICELIB Version 1.4.0, 09-SEP-2013 (BVS)

        Updated to keep track of the POOL counter and call ZZCVPOOL.

    SPICELIB Version 1.3.0, 05-MAR-2009 (NJB)

        This routine now keeps track of whether its kernel pool
        look-up failed. If so, a kernel pool lookup is attempted on
        the next call to this routine. This change is an enhancement,
        not a bug fix (unlike similar modifications in SCLK routines).

    SPICELIB Version 1.2.1, 15-NOV-2006 (EDW) (NJB)

        Replaced references to LDPOOL with references to FURNSH.
        Replaced references to RTPOOL with references to GDPOOL.
        Enhanced long error message associated with missing kernel
        variables.

    SPICELIB Version 1.2.0, 17-FEB-1999 (WLT)

        Added a second call to SWPOOL in the event some required
        kernel pool variable is not supplied.

    SPICELIB Version 1.1.0, 17-MAY-1994 (HAN)

        If the value of the function RETURN is .TRUE. upon execution of
        this module, this function is assigned a default value of
        either 0, 0.0D0, .FALSE., or blank depending on the type of
        the function.

    SPICELIB Version 1.0.0, 28-MAR-1992 (WLT)
Fri Dec 31 18:37:04 2021