License | GPL-2 |
---|---|
Maintainer | swiss-ephemeris@lfborjas.com |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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 a few select functions that are useful for western horoscopy are exported. There's a wealth of other calculations possible with the underlying library, however, please refer to their documentation and the bundled sources for ideas!
Synopsis
- data JulianTime
- data SiderealTime
- type HouseCusp = Double
- data Planet
- data HouseSystem
- data ZodiacSignName
- data EclipticPosition = EclipticPosition {}
- data EquatorialPosition = EquatorialPosition {}
- data GeographicPosition = GeographicPosition {}
- data HousePosition = HousePosition {}
- data ObliquityInformation = ObliquityInformation {}
- data Angles = Angles {}
- data CuspsCalculation = CuspsCalculation {
- houseCusps :: [HouseCusp]
- angles :: Angles
- systemUsed :: HouseSystem
- data LongitudeComponents = LongitudeComponents {}
- setEphemeridesPath :: FilePath -> IO ()
- setNoEphemeridesPath :: IO ()
- closeEphemerides :: IO ()
- withEphemerides :: FilePath -> IO a -> IO a
- withoutEphemerides :: IO a -> IO a
- calculateEclipticPosition :: JulianTime -> Planet -> IO (Either String EclipticPosition)
- calculateEquatorialPosition :: JulianTime -> Planet -> IO (Either String EquatorialPosition)
- calculateObliquity :: JulianTime -> IO (Either String ObliquityInformation)
- calculateCusps :: HouseSystem -> JulianTime -> GeographicPosition -> IO CuspsCalculation
- calculateCuspsLenient :: HouseSystem -> JulianTime -> GeographicPosition -> IO CuspsCalculation
- calculateCuspsStrict :: HouseSystem -> JulianTime -> GeographicPosition -> IO (Either String CuspsCalculation)
- equatorialToEcliptic :: ObliquityInformation -> EquatorialPosition -> EclipticPosition
- eclipticToEquatorial :: ObliquityInformation -> EclipticPosition -> EquatorialPosition
- calculateSiderealTime :: JulianTime -> ObliquityInformation -> IO SiderealTime
- calculateSiderealTimeSimple :: JulianTime -> IO SiderealTime
- calculateHousePosition :: HouseSystem -> Double -> GeographicPosition -> ObliquityInformation -> EclipticPosition -> IO (Either String HousePosition)
- calculateHousePositionSimple :: HouseSystem -> JulianTime -> GeographicPosition -> EclipticPosition -> IO (Either String HousePosition)
- julianDay :: Int -> Int -> Int -> Double -> JulianTime
- deltaTime :: JulianTime -> IO Double
- splitDegrees :: Double -> LongitudeComponents
- splitDegreesZodiac :: Double -> LongitudeComponents
Documentation
data JulianTime Source #
Represents an instant in Julian time.
see:
8. Date and time conversion functions
also cf. julianDay
Instances
Eq JulianTime Source # | |
Defined in SwissEphemeris.Internal (==) :: JulianTime -> JulianTime -> Bool # (/=) :: JulianTime -> JulianTime -> Bool # | |
Ord JulianTime Source # | |
Defined in SwissEphemeris.Internal compare :: JulianTime -> JulianTime -> Ordering # (<) :: JulianTime -> JulianTime -> Bool # (<=) :: JulianTime -> JulianTime -> Bool # (>) :: JulianTime -> JulianTime -> Bool # (>=) :: JulianTime -> JulianTime -> Bool # max :: JulianTime -> JulianTime -> JulianTime # min :: JulianTime -> JulianTime -> JulianTime # | |
Show JulianTime Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> JulianTime -> ShowS # show :: JulianTime -> String # showList :: [JulianTime] -> ShowS # |
data SiderealTime Source #
Represents an instant in sidereal time
Instances
Eq SiderealTime Source # | |
Defined in SwissEphemeris.Internal (==) :: SiderealTime -> SiderealTime -> Bool # (/=) :: SiderealTime -> SiderealTime -> Bool # | |
Ord SiderealTime Source # | |
Defined in SwissEphemeris.Internal compare :: SiderealTime -> SiderealTime -> Ordering # (<) :: SiderealTime -> SiderealTime -> Bool # (<=) :: SiderealTime -> SiderealTime -> Bool # (>) :: SiderealTime -> SiderealTime -> Bool # (>=) :: SiderealTime -> SiderealTime -> Bool # max :: SiderealTime -> SiderealTime -> SiderealTime # min :: SiderealTime -> SiderealTime -> SiderealTime # | |
Show SiderealTime Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> SiderealTime -> ShowS # show :: SiderealTime -> String # showList :: [SiderealTime] -> ShowS # |
type HouseCusp = Double Source #
The cusp of a given "house" or "sector". It is an ecliptic longitude. see: 14.1 House cusp calculation and 6.2 Astrological house systems
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
Sun | |
Moon | |
Mercury | |
Venus | |
Mars | |
Jupiter | |
Saturn | |
Uranus | |
Neptune | |
Pluto | |
MeanNode | |
TrueNode | |
MeanApog | |
OscuApog | |
Earth | |
Chiron |
Instances
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
data ZodiacSignName Source #
Represents western zodiac signs. Unless otherwise stated, they correspond to tropical divisions of the ecliptic, vs. the actual constellations.
Instances
data EclipticPosition Source #
Position data for a celestial body on the ecliptic, includes rotational speeds. see: 3.4 Position and speed
Instances
data EquatorialPosition Source #
Represents a position on the celestial sphere, with speed information included.
EquatorialPosition | |
|
Instances
data GeographicPosition Source #
Represents a point on Earth, with negative values for latitude meaning South, and negative values for longitude meaning West. No speed information is included (or needed,) because all calculations are geocentric.
Instances
data HousePosition Source #
The house a celestial body is in.
Instances
Eq HousePosition Source # | |
Defined in SwissEphemeris.Internal (==) :: HousePosition -> HousePosition -> Bool # (/=) :: HousePosition -> HousePosition -> Bool # | |
Show HousePosition Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> HousePosition -> ShowS # show :: HousePosition -> String # showList :: [HousePosition] -> ShowS # | |
Generic HousePosition Source # | |
Defined in SwissEphemeris.Internal type Rep HousePosition :: Type -> Type # from :: HousePosition -> Rep HousePosition x # to :: Rep HousePosition x -> HousePosition # | |
type Rep HousePosition Source # | |
Defined in SwissEphemeris.Internal type Rep HousePosition = D1 (MetaData "HousePosition" "SwissEphemeris.Internal" "swiss-ephemeris-1.1.0.0-Bh0UUxGPUDz5VNMbiTV5f1" False) (C1 (MetaCons "HousePosition" PrefixI True) (S1 (MetaSel (Just "houseNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "houseCuspDistance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))) |
data ObliquityInformation Source #
Includes the obliquity of the ecliptic, the Nutation as longitude as well as mean values.
Instances
Relevant angles: ascendant and MC, plus other "exotic" ones: 14. House cusp calculation
Angles | |
|
Instances
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.)
CuspsCalculation | |
|
Instances
data LongitudeComponents Source #
A longitude expressed in its constituent parts.
Instances
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.
calculateEclipticPosition :: JulianTime -> Planet -> IO (Either String EclipticPosition) 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.
calculateEquatorialPosition :: JulianTime -> Planet -> IO (Either String EquatorialPosition) Source #
Obtain equatorial position (includes declination) of a planet.
If you've called calculateEclipticPosition
in your code, this is a very cheap call, as the data
is already available to the C code.
calculateObliquity :: JulianTime -> IO (Either String ObliquityInformation) Source #
Given a time, calculate ecliptic obliquity and nutation
calculateCusps :: HouseSystem -> JulianTime -> GeographicPosition -> IO CuspsCalculation Source #
Alias for calculateCuspsLenient
calculateCuspsLenient :: HouseSystem -> JulianTime -> GeographicPosition -> IO CuspsCalculation Source #
Given a decimal representation of Julian Time (see julianDay
),
a GeographicPosition
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 -> GeographicPosition -> IO (Either String CuspsCalculation) Source #
Unlike calculateCuspsLenient
, return a Left
value if the required house system
couldn't be used to perform the calculations.
equatorialToEcliptic :: ObliquityInformation -> EquatorialPosition -> EclipticPosition Source #
Convert from an equatorial position to an ecliptic position. Requires
knowledge of obliquity (see calculateObliquity
.)
eclipticToEquatorial :: ObliquityInformation -> EclipticPosition -> EquatorialPosition Source #
Convert from an ecliptic position to an equatorial position. Requires
knowledge of obliquity (see calculateObliquity
.)
calculateSiderealTime :: JulianTime -> ObliquityInformation -> IO SiderealTime Source #
Given a JulianTime
and ObliquityInformation
, calculate the equivalent SiderealTime
.
prefer it over calculateSiderealTimeSimple
if you already obtained ObliquityInformation
for another calculation.
calculateSiderealTimeSimple :: JulianTime -> IO SiderealTime Source #
Given JulianTime
, 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
.
calculateHousePosition :: HouseSystem -> Double -> GeographicPosition -> ObliquityInformation -> EclipticPosition -> IO (Either String HousePosition) Source #
If you happen to have the correct ARMC for a time and place (obtained from calculateCusps)
and obliquity and nutation,
you can use this method to calculate a planet's house position.
Usually, what you have is just the time and place of the event, and positions of a planet,
in those cases, see calculateHousePositionSimple
.
calculateHousePositionSimple :: HouseSystem -> JulianTime -> GeographicPosition -> EclipticPosition -> IO (Either String HousePosition) Source #
Calculates the house position of a body in a house in the given system.
requires the geographic coordinates and time of the birth/event, and the
ecliptic coordinates of the planet/body. You only want this function if
you're working in the polar circle, or with objects that are way off the ecliptic;
for most objects in usual astrological charts, simply seeing which cusps
a planet falls between is sufficient, no need for this more complicated method.
see https://groups.io/g/swisseph/message/4052
NOTES: for the Koch system, this is likely to fail, or return counterintuitive
results. Also, we're doing a bit of a funky conversion between sidereal time and
ARMC, if you calculateCusps
, the correct armc
will be present in the returned Angles
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.
deltaTime :: JulianTime -> IO Double Source #
Given a JulianTime
(based on a UniversalTime), calculate the delta
between it and "true time":
See 7. Delta T
It relies on ephemeris data being open, and as such belongs in IO.
NOTE: this could be used to create a JulianTime -> EphemerisTime
function to send down to swe_calc
, if we choose to port that one.
splitDegrees :: Double -> LongitudeComponents Source #
Given a longitude, return the degrees from zero, minutes, seconds and seconds fraction.
splitDegreesZodiac :: Double -> LongitudeComponents Source #
Given a longitude, return the degrees it's from its nearest sign, minutes, seconds and seconds fraction.