swiss-ephemeris-1.0.0.0: Haskell bindings for the Swiss Ephemeris C library

LicenseGPL-2
Maintainerswiss-ephemeris@lfborjas.com
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

SwissEphemeris

Description

Exposes types and functions that mirror the rich functionality of Swiss Ephemeris. Currently only certain bodies are exposed as data constructors, same for the major house systems. This is for the sake of simplicity only, if you need more, please refer to the bundled header files in csrc.

You'll need to procure ephemeris files (see the official site, linked above) if you wish to obtain positions for planets outside of the main planetary bodies in the solar system, or before 3000 B.C or after 3000 A.D. For example, the test suite uses a small ephemeris that includes data for the asteroid Chiron, which is astrologically relevant in most modern practices.

Currently, only calculateCoordinates (to calculate the geocentric position of a given celestial body at a given Julian time,) and calculateCusps (to calculate house cusps and relevant angles in various house systems/traditions) are provided; plus a small julianDay function to translate between gregorian and julian times. There's a wealth of other calculations possible with the underlying library, please refer to their documentation and the bundled sources for ideas!

Synopsis

Documentation

data Planet Source #

All bodies for which a position can be calculated. Covers planets in the solar system, points between the Earth and the Moon, and astrologically significant asteroids (currently, only Chiron, but ephemerides data is available for others.) More at 2.1 Planetary and lunar ephemerides and 3.2 bodies

Instances
Enum Planet Source # 
Instance details

Defined in SwissEphemeris

Eq Planet Source # 
Instance details

Defined in SwissEphemeris

Methods

(==) :: Planet -> Planet -> Bool #

(/=) :: Planet -> Planet -> Bool #

Ord Planet Source # 
Instance details

Defined in SwissEphemeris

Show Planet Source # 
Instance details

Defined in SwissEphemeris

Generic Planet Source # 
Instance details

Defined in SwissEphemeris

Associated Types

type Rep Planet :: Type -> Type #

Methods

from :: Planet -> Rep Planet x #

to :: Rep Planet x -> Planet #

type Rep Planet Source # 
Instance details

Defined in SwissEphemeris

type Rep Planet = D1 (MetaData "Planet" "SwissEphemeris" "swiss-ephemeris-1.0.0.0-4niXG4kLJk84Lrc5WOeKSF" False) ((((C1 (MetaCons "Sun" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Moon" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Mercury" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Venus" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Mars" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Jupiter" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Saturn" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Uranus" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Neptune" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Pluto" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MeanNode" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TrueNode" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "MeanApog" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OscuApog" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Earth" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Chiron" PrefixI False) (U1 :: Type -> Type)))))

data HouseSystem Source #

The major house systems. The underlying library supports many more, including the 36-cusp outlier Gauquelin. More info at 6.2 Astrological house systems and 14. House cusp calculation

Instances
Enum HouseSystem Source # 
Instance details

Defined in SwissEphemeris

Eq HouseSystem Source # 
Instance details

Defined in SwissEphemeris

Ord HouseSystem Source # 
Instance details

Defined in SwissEphemeris

Show HouseSystem Source # 
Instance details

Defined in SwissEphemeris

Generic HouseSystem Source # 
Instance details

Defined in SwissEphemeris

Associated Types

type Rep HouseSystem :: Type -> Type #

type Rep HouseSystem Source # 
Instance details

Defined in SwissEphemeris

type Rep HouseSystem = D1 (MetaData "HouseSystem" "SwissEphemeris" "swiss-ephemeris-1.0.0.0-4niXG4kLJk84Lrc5WOeKSF" False) ((C1 (MetaCons "Placidus" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Koch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Porphyrius" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Regiomontanus" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Campanus" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Equal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WholeSign" PrefixI False) (U1 :: Type -> Type))))

type JulianTime = Double Source #

Represents an instant in Julian time. see: 8. Date and time conversion functions also cf. julianDay

type HouseCusp = Double Source #

The cusp of a given "house" or "sector" see: 14.1 House cusp calculation and 6.2 Astrological house systems

data Coordinates Source #

Position data for a celestial body, includes rotational speeds. see: 3.4 Position and speed

data Angles Source #

Relevant angles: ascendant and MC, plus other "exotic" ones: 14. House cusp calculation

Instances
Eq Angles Source # 
Instance details

Defined in SwissEphemeris

Methods

(==) :: Angles -> Angles -> Bool #

(/=) :: Angles -> Angles -> Bool #

Show Angles Source # 
Instance details

Defined in SwissEphemeris

Generic Angles Source # 
Instance details

Defined in SwissEphemeris

Associated Types

type Rep Angles :: Type -> Type #

Methods

from :: Angles -> Rep Angles x #

to :: Rep Angles x -> Angles #

type Rep Angles Source # 
Instance details

Defined in SwissEphemeris

data CuspsCalculation Source #

Result of calculating the cusps for a given event; will include a list of cusps (most systems use 12 cusps, Gauquelin uses 36.)

Instances
Eq CuspsCalculation Source # 
Instance details

Defined in SwissEphemeris

Show CuspsCalculation Source # 
Instance details

Defined in SwissEphemeris

Generic CuspsCalculation Source # 
Instance details

Defined in SwissEphemeris

Associated Types

type Rep CuspsCalculation :: Type -> Type #

type Rep CuspsCalculation Source # 
Instance details

Defined in SwissEphemeris

type Rep CuspsCalculation = D1 (MetaData "CuspsCalculation" "SwissEphemeris" "swiss-ephemeris-1.0.0.0-4niXG4kLJk84Lrc5WOeKSF" False) (C1 (MetaCons "CuspsCalculation" PrefixI True) (S1 (MetaSel (Just "houseCusps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [HouseCusp]) :*: (S1 (MetaSel (Just "angles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Angles) :*: S1 (MetaSel (Just "systemUsed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HouseSystem))))

defaultCoordinates :: Coordinates Source #

Default coordinates with all zeros -- when you don't care about/know the velocities, which would be the case for most inputs (though most outputs will include them.) Usually you'll set only lat and lng (e.g. defaultCoordinates{lat = 1.4, lng = 4.1}) when using it as an input for another function.

mkCoordinates :: Coordinates Source #

Constructor alias of defaultCoordinates, since it's used a lot in that role.

julianDay :: Int -> Int -> Int -> Double -> JulianTime Source #

Given year, month and day as Int and a time as Double, return a single floating point number representing absolute JulianTime. The input date is assumed to be in Gregorian time.

setEphemeridesPath :: FilePath -> IO () Source #

Given a path to a directory, point the underlying ephemerides library to it. You only need to call this function to provide an explicit ephemerides path, if the environment variable SE_EPHE_PATH is set, it overrides this function.

setNoEphemeridesPath :: IO () Source #

Explicitly state that we don't want to set an ephemeris path, which will default to the built-in ephemeris, or use the directory in the SE_EPHE_PATH environment variable, if set.

closeEphemerides :: IO () Source #

Explicitly release all "cache" pointers and open files obtained by the C library.

withEphemerides :: FilePath -> IO a -> IO a Source #

Run a computation with a given ephemerides path open, and then close it. Note that the computation does not receive the ephemerides, in keeping with the underlying library's side-effectful conventions.

withoutEphemerides :: IO a -> IO a Source #

Run a computation with no explicit ephemerides set, if the SE_EPHE_PATH environment variable is set, that will be used. If not, it'll fall back to in-memory data.

calculateCoordinates :: JulianTime -> Planet -> IO (Either String Coordinates) Source #

Given JulianTime (see julianDay), and a Planet, returns either the position of that planet at the given time, if available in the ephemeris, or an error. The underlying library may do IO when reading ephemerides data.

calculateCuspsLenient :: HouseSystem -> JulianTime -> Coordinates -> IO CuspsCalculation Source #

Given a decimal representation of Julian Time (see julianDay), a set of Coordinates (see mkCoordinates,) and a HouseSystem (most applications use Placidus,) return a CuspsCalculation with all house cusps in that system, and other relevant Angles. Notice that certain systems, like Placidus and Koch, are very likely to fail close to the polar circles; in this and other edge cases, the calculation returns cusps in the Porphyrius system. The underlying library may do IO when consulting ephemerides data.

calculateCuspsStrict :: HouseSystem -> JulianTime -> Coordinates -> IO (Either String CuspsCalculation) Source #

Unlike calculateCuspsLenient, return a Left value if the required house system couldn't be used to perform the calculations.