Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Planet
- data HouseSystem
- type JulianTime = Double
- data Coordinates = Coordinates {}
- data HouseCusps = HouseCusps {}
- data Angles = Angles {}
- data CuspsCalculation = CuspsCalculation {
- houseCusps :: HouseCusps
- angles :: Angles
- defaultCoordinates :: Coordinates
- setEphemeridesPath :: String -> IO ()
- closeEphemerides :: IO ()
- withEphemerides :: FilePath -> IO a -> IO a
- julianDay :: Int -> Int -> Int -> Double -> JulianTime
- calculateCoordinates :: JulianTime -> Planet -> Either String Coordinates
- calculateCusps :: JulianTime -> Coordinates -> HouseSystem -> Either String CuspsCalculation
- calculateCoordinatesM :: MonadFail m => JulianTime -> Planet -> m Coordinates
- calculateCuspsM :: MonadFail m => JulianTime -> Coordinates -> HouseSystem -> m CuspsCalculation
Documentation
Sun | |
Moon | |
Mercury | |
Venus | |
Mars | |
Jupiter | |
Saturn | |
Uranus | |
Neptune | |
Pluto | |
MeanNode | |
TrueNode | |
MeanApog | |
OscuApog | |
Earth | |
Chiron |
Instances
data HouseSystem Source #
Instances
type JulianTime = Double Source #
data Coordinates Source #
Instances
data HouseCusps Source #
Instances
Angles | |
|
Instances
data CuspsCalculation Source #
Instances
Eq CuspsCalculation Source # | |
Defined in SwissEphemeris (==) :: CuspsCalculation -> CuspsCalculation -> Bool # (/=) :: CuspsCalculation -> CuspsCalculation -> Bool # | |
Show CuspsCalculation Source # | |
Defined in SwissEphemeris showsPrec :: Int -> CuspsCalculation -> ShowS # show :: CuspsCalculation -> String # showList :: [CuspsCalculation] -> ShowS # | |
Generic CuspsCalculation Source # | |
Defined in SwissEphemeris type Rep CuspsCalculation :: Type -> Type # from :: CuspsCalculation -> Rep CuspsCalculation x # to :: Rep CuspsCalculation x -> CuspsCalculation # | |
type Rep CuspsCalculation Source # | |
Defined in SwissEphemeris type Rep CuspsCalculation = D1 (MetaData "CuspsCalculation" "SwissEphemeris" "swiss-ephemeris-0.2.0.0-FojOtb27jUL7cJU6ugvevj" False) (C1 (MetaCons "CuspsCalculation" PrefixI True) (S1 (MetaSel (Just "houseCusps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HouseCusps) :*: S1 (MetaSel (Just "angles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Angles))) |
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.
setEphemeridesPath :: String -> IO () Source #
Given an *absolute* path, point the underlying ephemerides library to it.
Takes a String
for easy use with the directory
package.
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.
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.
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 Julian Time.
The input date is assumed to be in Gregorian time.
More info on this:
https://www.astro.com/swisseph/swephprg.htm#_Toc46406824
calculateCoordinates :: JulianTime -> Planet -> Either String Coordinates Source #
Given a decimal representation of Julian Time (see julianDay
),
and a Planet
, returns either the position of that planet at the given time,
if available in the ephemeris, or an error.
calculateCusps :: JulianTime -> Coordinates -> HouseSystem -> Either String CuspsCalculation Source #
Given a decimal representation of Julian Time (see julianDay
),
and a set of Coordinates
(see calculateCoordinates
,) and a HouseSystem
(most applications use Placidus
,) return either CuspsCalculation
with all 12
house cusps in that system, and other relevant Angles
, or an error.
calculateCoordinatesM :: MonadFail m => JulianTime -> Planet -> m Coordinates Source #
MonadFail
version of calculateCoordinates
, in case you don't particularly care
about the error message (since it's likely to be due to misconfigured ephe files)
and want it to play nice with other MonadFail
computations.
calculateCuspsM :: MonadFail m => JulianTime -> Coordinates -> HouseSystem -> m CuspsCalculation Source #
MonadFail
version of calculateCusps
, in case you don't particularly care about
the error message (there's only one error scenario currently: inability to
determine cusps, in coordinates not contemplated by the given house system.)