swiss-ephemeris-1.4.2.0: Haskell bindings for the Swiss Ephemeris C library
LicenseAGPL-3
Maintainerswiss-ephemeris@lfborjas.com
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

SwissEphemeris.Time

Description

Functions and types for conversion between Haskell time types and Swiss Ephemeris time values.

Since: 1.4.0.0

Synopsis

The many faces of time

This module offers conversions between some Haskell time values, and astronomical time values as defined by SwissEphemeris. The most important types in this module are TimeStandard, which refers to different "standards" of time such as Universal Time and Terrestial Time, and JulianDay, which codifies an absolute floating point number of fractional "days" since an epoch in the distant past. A SiderealTime is also provided, though it figures less prominently in the Swiss Ephemeris API, and the conversions are more self-explanatory.

As far as this library is concerned, a Julian Day can represent either a moment in Universal Time, which takes into account the Earth's rotation (either the more specific UT1 standard, or a generic UT time whose precision is left up to the caller -- we provide ways of converting a UTCTime into a JulianDayUT, for example,) or Terrestrial Time, which is independent of the Earth's rotation and is used in astronomical measurements from a theoretical point on the surface of the Earth. Most functionality in Swiss Ephemeris uses Terrestrial Time (the documentation also refers to it using the now-superseded moniker of Ephemeris Time, but current versions of the library actually don't use the time standard by that name, and instead adhere to TT.)

An absolute moment in time will not be the same in UT1 and TT: TT is ahead of UT1 by a quantity known as Delta Time, which is not neatly predictable but which is expected to increase with the passage of time; given this reality, functions in this module make it mostly impossible to "coerce" a Julian Day obtained from a moment in Universal Time to Terrestrial Time (and vice-versa: ) Delta Time must be calculated, and leap seconds in UT must be taken into account. Swiss Ephemeris provides functions to do these conversions safely by consulting historical data (hence the IO restriction,) and the ToJulian and FromJulian typeclasses govern the interface for conversion for any given type: currently only UTCTime from the Haskell time taxonomy is supported: a Day can trivially be first converted to/from UTCTime, and other values such as Haskell's own notion of UniversalTime don't have immediate astronomical significance.

The only somewhat "safe" coercion between time standards that doesn't go through IO is between UT and UT1, though for UTCTime, this will be off by less than a second due to the nature of UTC vs. UT1.

For convenience, we provide a way of converting between Day and any JulianDay values purely, which relies on temporally unsound assumptions about the difference between the supported time standards; this works fine for dates, but is categorically wrong whenever a time of day is necessary. Go through the typeclass methods in that case.

Some further reading:

data TimeStandard Source #

Various standards for measuring time that can be expressed as Julian Days.

Constructors

TT

Terrestrial Time (successor to Ephemeris Time)

UT1

Universal Time, explicitly in its UT1 form.

UT

Universal Time, in any of its forms; depending on how it was constructed (in most cases, UTC)

Instances

Instances details
Eq TimeStandard Source # 
Instance details

Defined in SwissEphemeris.Time

Show TimeStandard Source # 
Instance details

Defined in SwissEphemeris.Time

data JulianDay (s :: TimeStandard) Source #

A JulianDay can have different provenances, witnessed by its accompanying phantom type:

  • It could've been converted, purely, from a UTC value, as such, its witness is UT
  • It could'be been produced by consulting tidal/leap second information, as done by the Swiss Ephemeris library, in which case it's TT (aka, somewhat wrongly, as Ephemeris time,) or UT1.

Instances

Instances details
Enum (JulianDay s) Source # 
Instance details

Defined in SwissEphemeris.Time

Eq (JulianDay s) Source # 
Instance details

Defined in SwissEphemeris.Time

Methods

(==) :: JulianDay s -> JulianDay s -> Bool #

(/=) :: JulianDay s -> JulianDay s -> Bool #

Ord (JulianDay s) Source # 
Instance details

Defined in SwissEphemeris.Time

Show (JulianDay s) Source # 
Instance details

Defined in SwissEphemeris.Time

type JulianDayUT = JulianDay 'UT Source #

A generic universal time as a Julian Day

type JulianDayTT = JulianDay 'TT Source #

A terrestrial time as a Julian Day

type JulianDayUT1 = JulianDay 'UT1 Source #

A UT1 universal time as a Julian Day

getJulianDay :: JulianDay s -> Double Source #

Get the underlying Double in a JulianDay. We intentionally do not export a way to finagle a Double into a JulianDay: you'll have to obtain it through the various temporal conversion functions.

singletons

data SingTimeStandard :: TimeStandard -> Type where Source #

Singletons for pseudo-dependent type programming with time standards.

class SingTSI a where Source #

Typeclass to recover the singleton for a given time standard

Instances

Instances details
SingTSI 'TT Source # 
Instance details

Defined in SwissEphemeris.Time

SingTSI 'UT1 Source # 
Instance details

Defined in SwissEphemeris.Time

SingTSI 'UT Source # 
Instance details

Defined in SwissEphemeris.Time

Impure conversion typeclasses

class MonadFail m => ToJulianDay m jd from where Source #

Conversion from a temporal value of type from to a JulianDay in the TimeStandard jd. It's bound to IO _and_ a containing MonadFail since in the general case, we need to interact with the outside world, and may fail, when consulting the necessary data. How can it fail? In short: at least for valid temporal values constructed via the time library, pretty much only if you have an old version of Swiss Ephemeris that's not aware of a recent leap second.

Methods

toJulianDay :: from -> IO (m (JulianDay jd)) Source #

Instances

Instances details
MonadFail m => ToJulianDay m 'TT UTCTime Source # 
Instance details

Defined in SwissEphemeris.Time

Methods

toJulianDay :: UTCTime -> IO (m (JulianDay 'TT)) Source #

MonadFail m => ToJulianDay m 'UT1 UTCTime Source # 
Instance details

Defined in SwissEphemeris.Time

Methods

toJulianDay :: UTCTime -> IO (m (JulianDay 'UT1)) Source #

MonadFail m => ToJulianDay m 'UT UTCTime Source # 
Instance details

Defined in SwissEphemeris.Time

Methods

toJulianDay :: UTCTime -> IO (m (JulianDay 'UT)) Source #

class FromJulianDay jd to where Source #

Conversion from a JulianDay in the TimeStandard jd to a temporal value of type to It's bound to IO since historical data may need to be consulted; however, as per the underlying library, it cannot fail.

Methods

fromJulianDay :: JulianDay jd -> IO to Source #

Instances

Instances details
FromJulianDay 'TT UTCTime Source # 
Instance details

Defined in SwissEphemeris.Time

FromJulianDay 'UT1 UTCTime Source # 
Instance details

Defined in SwissEphemeris.Time

FromJulianDay 'UT UTCTime Source # 
Instance details

Defined in SwissEphemeris.Time

Wrapper for fail-able conversions

data ConversionResult dt Source #

A type that encodes an attempt to convert between temporal types.

Pure utility functions

mkJulianDay :: SingTimeStandard ts -> Double -> JulianDay ts Source #

Constructor with chaperone: you have to provide a witness to a time standard to produce a JulianDay directly from a Double. This is mostly intended for internal use, if you find yourself using this function, you're probably producing an unreliable value: consider using the ToJulianDay instance of a reliable temporal type (like UTCTime,) before reaching for this function.

coerceUT :: JulianDay 'UT -> JulianDay 'UT1 Source #

Coerce a value obtained directly from UTC (without consulting historical data) into a UT1 Julian Day. The difference should be less than 1 second, and if you've used Haskell's own UTCTime as the source it should be negligible for most use cases. If you want to be precise... you'll have to go into IO.

julianNoon :: JulianDay ts -> JulianDay ts Source #

Historically, Julian Days started at noon, which is why the point with no fractional part is noon (not midnight).

julianMidnight :: JulianDay ts -> JulianDay ts Source #

The half-day in Julian Days is midnight, so midnight of a given date is halfway through the _previous_ day.

Impure conversion functions

utcToJulianDays :: MonadFail m => UTCTime -> IO (m (JulianDay 'TT, JulianDay 'UT1)) Source #

Convert a UTCTime into a tuple of Terrestrial Time and UT1 Julian Days; the underlying C function can return errors if:

  • Any of the individual date components are invalid
  • The given date has a leap second that it is not aware of (due to either input error or the library not being out of date.)

A legitimately obtained UTCTime (i.e. not crafted by hand, but by some means of validated time input/ingestion) is very unlikely to error out in the former of those scenarios, but there is a chance it may fail in the latter; if you encounter this, the first step would be to update the Swiss Ephemeris library, since they bundle an array of leap seconds; otherwise, you can provide a file called seleapsec.txt in your configured ephemeris path, see: 8.3. Handling of leap seconds and the file seleapsec.txt

Pure conversion functions

Lossy conversion of a Day value

dayFromJulianDay :: JulianDay ts -> Day Source #

Convenience "pure" function that takes an arbitrary JulianDay value in any time standard, converts it to noon, and then to the corresponding 'Day.' Exploits the same circumstantial truths about time as dayToJulianDay

dayToJulianDay :: Day -> JulianDay ts Source #

Convenience "pure" function that pretends that a day at noon can be converted to any JulianDay; in reality, it pretends that a JulianDay in UT stands in for any other (e.g. in UT1 or TT) -- this is "good enough" for a day at noon since, at least in 2021, UT is only off by less than a second from UT1, and only behind TT by a few seconds

Fake (innacurate) conversions of datetime components

gregorianToFakeJulianDayTT :: Integer -> Int -> Int -> Double -> JulianDay 'TT Source #

If you care about accuracy, don't use this function!!! It's merely provided as a facility for testing or situations where you don't really care about the truth: the actual Julian Day produced by this function is an absolute, universal time, we just naughtily repackage it as a terrestrial time here. If you want a real TerrestrialTime, either convert a valid temporal value through the toJulianDay polymorphic function, or use universalToTerrestrial if you already have a UT1 value.

gregorianFromFakeJulianDayTT :: JulianDay 'TT -> (Integer, Int, Int, Double) Source #

This is a bit of a misnomer: the "fake" value isn't the input, it's the output: it produces a value as if the input was in UT, thus running afoul of both leap seconds and delta time. Only useful in contexts where accuracy is not valued. To get a somewhat more trustworthy value, and still not have to go into IO, check out dayFromJulianDay, which produces only the Day part of a date.

Lossy UT conversions of datetime components

gregorianToJulianDayUT :: Integer -> Int -> Int -> Double -> JulianDay 'UT Source #

Given components of a gregorian day (and time,) produce a JulianDay in the generic UT time standard; the precision of the resulting Julian Day will only be as good as its input; if obtained by other means than via a UTCTime, it's likely to be off by up to a second when compared with a UT1 value. (on the other hand, it doesn't consult any data so it's not bound to IO) This is provided for convenience, but if you have date components, you'd be better off producing a valid UTCTime to send to the toJulian family of functions, via e.g. fromGregorianValid and makeTimeOfDayValid

gregorianFromJulianDayUT :: JulianDay 'UT -> (Integer, Int, Int, Double) Source #

Given a JulianDay in UT, produce the equivalent Gregorian date's components.

Lossy UT conversions of an UTC value

utcToJulianDayUT :: UTCTime -> JulianDay 'UT Source #

Given a UTCTime, produce a JulianDay purely. It can only be said to be in UT, since Haskell's UTC is an approximation of UT1, off to up to a second. If you want precision, use utcToJulianDays (which returns both the UT1 and TT timestamps,) or utcToJulianUT1. Keep in mind though, that they're both in IO and may return errors.

julianDayUTToUTC :: JulianDay 'UT -> UTCTime Source #

Given a JulianDay in the vague UT time standard, produce a UTCTime purely.

utcToJulian :: UTCTime -> JulianDay 'UT Source #

See utcToJulianDayUT -- this function is provided for convenience in contexts where the ~1s accuracy gain is not worth the more complicated type signature of toJulian, but you'll get a "lesser" JulianDay that's only as precise as its input.

julianToUTC :: JulianDay 'UT -> UTCTime Source #

See julianDayUTToUTC -- this function is provided for convenience in contexts where a slightly innacurate JulianDay is worth it to stay in a pure context, otherwise, see fromJulian.

Delta Time

addDeltaTime :: JulianDay 'UT1 -> Double -> JulianDay 'TT Source #

Add time to catch up UT to TT; doesn't make sense for other time standards.

subtractDeltaTime :: JulianDay 'TT -> Double -> JulianDay 'UT1 Source #

Subtract time to 'slow down' TT to UT; doesn't make sense for other time standards.

unsafeDeltaTime :: JulianDay 'UT1 -> IO Double Source #

Somewhat naïve delta time calculation: if no ephemeris mode has been selected, it will use the default tidal acceleration value as per the DE431 JPL ephemeris, otherwise, it will use whatever ephemeris is currently set. It's considered unsafe since switching ephemeris modes will result in an incongruent delta time. See safeDeltaTime

safeDeltaTime :: MonadFail m => EphemerisOption -> JulianDay 'UT1 -> IO (m Double) Source #

Same as deltaTime, but fails if the given EphemerisOption doesn't agree with the current ephemeris mode.

deltaTimeSE :: MonadFail m => JulianDay 'UT1 -> IO (m Double) Source #

Try to produce a delta time for the SwissEphemeris ephemeris mode, will fail if the current mode isn't set to SwissEphemeris.

universalToTerrestrial :: JulianDay 'UT1 -> IO (JulianDay 'TT) Source #

Convert between an instant in UT1 to TT, as a JulianDay, may produce inaccurate results if an ephemeris mode isn't set explicitly.

universalToTerrestrialSafe :: MonadFail m => EphemerisOption -> JulianDay 'UT1 -> IO (m (JulianDay 'TT)) Source #

Convert between an instant in UT1 to TT, as a JulianDay, using an explicit ephemeris mode; fails if not currently working in the expected mode.

universalToTerrestrialSE :: MonadFail m => JulianDay 'UT1 -> IO (m (JulianDay 'TT)) Source #

universaltoTerrestrialSafe, set to SwissEphemeris

Sidereal time

julianToSiderealSimple :: JulianDay 'UT1 -> IO SiderealTime Source #

Given JulianDay, get SiderealTime. May consult ephemerides data, hence it being in IO, will have to calculate obliquity at the given julian time, so it'll be slightly slower than calculateSiderealTime.

julianToSidereal :: JulianDay 'UT1 -> ObliquityInformation -> IO SiderealTime Source #

Given a JulianDay and ObliquityInformation, calculate the equivalent SiderealTime. prefer it over calculateSiderealTimeSimple if you already obtained ObliquityInformation for another calculation.