License | AGPL-3 |
---|---|
Maintainer | swiss-ephemeris@lfborjas.com |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
SwissEphemeris.Precalculated
Description
Functions for interacting with pre-calculated, file-persisted
ephemeris. You're responsible for providing a location for
sep4_
formatted files, as produced by the current version of
this library, in a compatible architecture. This can be done either
by setting the EP4_PATH
environment variable to a valid directory path,
or via the setEph4Path
function.
Since: 1.4.0.0
Synopsis
- data EphemerisPosition a = EphemerisPosition {
- ephePlanet :: !Planet
- epheLongitude :: !a
- epheSpeed :: !a
- data Ephemeris a = Ephemeris {
- epheDate :: !JulianDayTT
- epheEcliptic :: !a
- epheNutation :: !a
- ephePositions :: !(Vector (EphemerisPosition a))
- data EphemerisBlockNumber
- type EpheVector = Vector Double
- data EpheCalcOption
- data PlanetListOption
- forPlanet :: Ephemeris a -> Planet -> Maybe (EphemerisPosition a)
- planetEphe :: Planet -> Ephemeris a -> Maybe (EphemerisPosition a)
- mkEphemerisBlockNumber :: Int -> Maybe EphemerisBlockNumber
- extractEphemerisBlockNumber :: EphemerisBlockNumber -> Int
- setEphe4Path :: FilePath -> IO ()
- readEphemeris :: (NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> EpheVector -> a) -> NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> IO (Either String a)
- readEphemerisStrict :: NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> IO (Either String (Ephemeris (Maybe Double)))
- readEphemerisSimple :: NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> IO (Either String (Ephemeris Double))
- readEphemerisEasy :: Bool -> JulianDayTT -> IO (Either String (Ephemeris Double))
- readEphemerisRaw :: PlanetListFlag -> EpheCalcFlag -> JulianDayTT -> IO (Either String EpheVector)
- readEphemerisRawNoFallback :: JulianDayTT -> IO (Either String EpheVector)
- writeEphemeris :: EphemerisBlockNumber -> IO (Either String EphemerisBlockNumber)
- foldEpheCalcOptions :: [EpheCalcFlag] -> EpheCalcFlag
- foldPlanetListOptions :: [PlanetListFlag] -> PlanetListFlag
About Precalculated Ephemeris
Pre-calculated Ephemeris are disk-persisted binary blocks of 10,000 days of positions each. They store planetary data in a space-efficient format, to the slight detriment of precision. Positions for all planets in the sol system (including Pluto, but excluding the heliocentric position of the Earth,) as well as the mean lunar apogee ("Black Moon Lilith",) the Mean and True [North] lunar nodes, and the asteroid Chiron as well as Ecliptic and Nutation for the day are stored in contiguous blocks.
Even though only midnight data
is actually stored (e.g. 2440000.5
,) the underlying library will
use a fast interpolation method to approximate any julian date requested of it,
it also uses that interpolation method to approximate the speeds of planets,
which are not stored.
The file format is designed for fast sequential access: a file pointer and
cursor survive invocations, and a buffer of 20 days of positions is maintained
in-memory, so requesting all days in a year will benefit vastly from memory
residency and outpace random access or actual ephemeris calculations. Some
care has been put into thread-safety, but the original implementation was not
thread safe, so even though I've run a lot of valgrind
after adding some
thread-local guardrails, here may be dragons if you do heavy threaded access
or heavy non-sequential querying. The regular SwissEphemeris
is battle-tested
for safety and speed, so use that for most use cases that don't need to quickly
examine large intervals of contiguous time quickly, which is the narrow province
of this module.
Deferring to the original authors' for more details:
Note from sweephe4.h
The design of ephemeris type ep4: In all ASYS and transit application of stored ephemerides except Progressed Declinations Type 56 we need only the longitudes of the planets or nodes. The old EP3 format contains also latitudes, and uses ephemeris time. Therefore we define a new ephemeris format, which is capable of replacing EP3, when some ASYS programs are changed. The ASYS programs requiring different data can receive them by asking the calcserv module.
We therefore store now a daily ephemeris with only logitudes, ecl and nut.
The ephemeris is computed and stored for midnight ephemeris time, i.e.
for jd = 2400000.5, 2400001.5
etc.
In the ephemeris record for this date, only floor(jd) is kept.
In many cases universal time (UT) is desired, not ephemeris time. Because computation with our current computers is very cheap for everything except trigonometrci functions, we can afford to build a good interpolation into the ephemeris package.
The user can request from ephread() ephemeris positions for any (double) jd, not only for midnight ephemeris time. Inside the package the same quick Everett 5th-order interpolator is used as in placalc. It delivers positions within 0.01" for all planets except moon, mercury and true node. Moon and Mercury suffer, because their positions are stored only with a precision of 0.1"; true node suffers because it oscillates quickly with the fastest moon terms. The maximum observed differences between placalc and ephread for 12.00 noon are 0.25" for moon and true node and 0.1" for Mercury; in 80% of the days the differences are less than 0.1". This is significantly better than the implemented precision of the placalc package itself.
The Everett interpolator delivers without any additional cost also the speed of the planets. This speed is very much better than the speed derived for the inner planets from the mean orbits.
The returned data from ephread are in an array of centisec,
with ecl and nut behind the planets.
The default, pflag = 0
, returns all.
The speeds are returned in the second half of the array;
the speed is always there, even when the speed bit has not been set.
data EphemerisPosition a Source #
The ecliptic longitude data of a given Planet
Constructors
EphemerisPosition | |
Fields
|
Instances
The positions of all planets for a given time, plus ecliptic and nutation.
Constructors
Ephemeris | |
Fields
|
Instances
Eq a => Eq (Ephemeris a) Source # | |
Show a => Show (Ephemeris a) Source # | |
Generic (Ephemeris a) Source # | |
type Rep (Ephemeris a) Source # | |
Defined in SwissEphemeris.Precalculated type Rep (Ephemeris a) = D1 ('MetaData "Ephemeris" "SwissEphemeris.Precalculated" "swiss-ephemeris-1.4.0.0-4yP55cKKPuSDh3BxO5EEXV" 'False) (C1 ('MetaCons "Ephemeris" 'PrefixI 'True) ((S1 ('MetaSel ('Just "epheDate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JulianDayTT) :*: S1 ('MetaSel ('Just "epheEcliptic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "epheNutation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "ephePositions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector (EphemerisPosition a)))))) |
data EphemerisBlockNumber Source #
Up to three-digit numbers assigned to each
10,000 day block of ephemeris data; any given
number will be padded with zeroes internally
to make up a Julian date, at midnight.
e.g. EphemerisBlocknumber 244
corresponds to jd = 2440000.5
, i.e.
1968-May-23 12:00:00 UTC
Instances
type EpheVector = Vector Double Source #
For extreme data locality, we schlep around unboxed vectors.
Note that the higher level functions return regular Vector
s,
to maintain some locality/performance, without awkward unboxing.
Options
Options for additional computations
data EpheCalcOption Source #
Options for additional computations that are allowed when reading a block of ephemeris.
Constructors
IncludeSpeed | |
MustUseStoredEphe |
Instances
Options for which positions to include.
data PlanetListOption Source #
Whether to include all planets, ecliptic, nutation, or all of the above. The underlying library also allows for bit flags to disable selecting some planets; I haven't though of a way to model that ergonomically.
Constructors
IncludeAllPlanets | |
IncludeEcliptic | |
IncludeNutation | |
IncludeAll |
Instances
Convenience functions
forPlanet :: Ephemeris a -> Planet -> Maybe (EphemerisPosition a) Source #
Convenience "indexing" function to get a given Planet
s
data from a given ephemeris.
planetEphe :: Planet -> Ephemeris a -> Maybe (EphemerisPosition a) Source #
Flipped version of forPlanet
mkEphemerisBlockNumber :: Int -> Maybe EphemerisBlockNumber Source #
Construct a valid ephemeris block number. As per the
underlying library, all times between Julian day -200000.0
and 3000000.0
are valid. Note that depending on which
ephemeris files you have, your effective range may be smaller,
or bigger. This is provided as a common denominator, but to get
the real range of your ephemeris, check out the swe_get_current_file_data
function.
(cf. section 2.6 of the manual)
extractEphemerisBlockNumber :: EphemerisBlockNumber -> Int Source #
Get the Int
inside an EphemerisBlockNumber
Setup functions
setEphe4Path :: FilePath -> IO () Source #
Set path for base directory where sep4_
files are stored.
WARNING: this is provided for convenience, but in a multi-threaded
situation, it is relatively likely that a call to this function will
either be optimized away, or interleaved too late. Please consider
setting the EP4_PATH
environment variable instead: it will always
be found by the C code, vs. the sometimes of Haskell's inscrutable
optimizations.
High-level read functions
readEphemeris :: (NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> EpheVector -> a) -> NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> IO (Either String a) Source #
Given a function to convert a vector of doubles to a type for ephemeris,
a list of PlanetListOption
, a list of EpheCalcOption
and a JulianDay
,
try to get ephemeris data from a precalculated file on disk, or, if
allowed in the specified options, fall back to regular Swiss
Ephemeris calculations, using the current ephemeris mode.
The authors of Swiss Ephemeris encourage always requesting all planets, ecliptic and nutation since they're stored in contiguous blocks anyway, and the implementation calculates speeds always so omitting speed isn't worthwhile apart from data hygiene, or when choosing to allow falling back to non-stored calculations.
Make sure you set the EP4_PATH
environment variable, or call
setEphe4Path
before calling this function, otherwise the
underlying library will try to locate the files in homeephe/
.
readEphemerisStrict :: NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> IO (Either String (Ephemeris (Maybe Double))) Source #
A version of readEphemeris
that wraps all longitudes, speeds,
ecliptic and nutation in Maybe
s: if a given planet is configured
to be skipped, its longitude will be Nothing
; same for all speeds,
ecliptic and nutation if the respective options are set.
readEphemerisSimple :: NonEmpty PlanetListOption -> NonEmpty EpheCalcOption -> JulianDayTT -> IO (Either String (Ephemeris Double)) Source #
A version of readEphemeris
that always includes all planets and all
speeds, as well as ecliptic and nutation.
readEphemerisEasy :: Bool -> JulianDayTT -> IO (Either String (Ephemeris Double)) Source #
A version of readEphemeris
that always gets all planets,
ecliptic and nutation, always includes speed,
and allows falling back to non-stored
swe_calc
for dates/planets outside of the stored range (
via the allowFallback
Bool
parameter.)
I recommend using this one: as mentioned elsewhere, the underlying library will always calculate all ephemeris and all speeds, the only material difference is that if it has to fall back to the underlying ephemeris, it _will_ skip calculating any specified planets or speeds. I personally use the "no fallback" version.
Low-level read functions
readEphemerisRaw :: PlanetListFlag -> EpheCalcFlag -> JulianDayTT -> IO (Either String EpheVector) Source #
Lower-level version of readEphemeris
:
- Expects options as bit flags set in a
PlanetListFlag
; idem forEpheCalcFlag
options. This is useful if one really wants to get into the setting bit flags to select planets adventure. - Returns a simple unboxed vector of
Double
s, where the firstnumberOfFactors
elements are the planets, ecliptic and nutation; and the rest are speeds. (the underlying library always returns the full array, but if planets ecliptic, nutation or ommitted, they won't be populated.) - The underlying implementation uses a
static
array, which means that between invocations, quantities that are not calculated again linger (e.g. you asked for all planets, all speeds, ecliptic and nutation in one pass, and then only ask for certain planets, no speeds, no ecl/nut: the previous values for these will be there!) I've left it as-is here, but made the behavior more predictable inreadEphemeris
.
Due to the somewhat leaky/tricky nature of the underlying interface, this
function is provided merely for experimental usage -- you very likely want
readEphemeris
!
readEphemerisRawNoFallback :: JulianDayTT -> IO (Either String EpheVector) Source #
For the most basic case: read ephemeris without falling back to the non-stored variant, and always include speeds, all planets, ecliptic and nutation.
Generating new ephemeris files
writeEphemeris :: EphemerisBlockNumber -> IO (Either String EphemerisBlockNumber) Source #
Persist a 10,000 day block of ephemeris to disk, given a julian prefix.
This is a highly side-effectful function:
- It assumes you've set usable paths to both the
sep4
files and usable ephemeris. ALeft
value will be returned otherwise. - It is not friendly to repeated invocations: if you happen to run it in sequence with the same block number, undefined behavior may arise where the file is still "open" as far as the underlying library is concerned, because it keeps its own cursor, but the file descriptior will be closed. We can fix that, but it introduces a divergence in the code that I'd rather just warn about for the time being.
Low-level utils
foldEpheCalcOptions :: [EpheCalcFlag] -> EpheCalcFlag Source #
Fold any given flags into one number with the combined flags set.
foldPlanetListOptions :: [PlanetListFlag] -> PlanetListFlag Source #
Fold any given planet flags into one datum with the combined flags set.