| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Foreign.SwissEphemeris
Description
Exposes very low-level FFI bindings to the C library. Use the SwissEphemeris module and its more
Haskell-friendly exports.
Synopsis
- newtype PlanetNumber = PlanetNumber {}
- newtype EpheFlag = EpheFlag {
- unEpheFlag :: CInt
- newtype GregFlag = GregFlag {
- unGregFlag :: CInt
- newtype CalcFlag = CalcFlag {
- unCalcFlag :: CInt
- newtype SplitDegFlag = SplitDegFlag {}
- newtype EclipseFlag = EclipseFlag {}
- sun :: PlanetNumber
- moon :: PlanetNumber
- mercury :: PlanetNumber
- venus :: PlanetNumber
- mars :: PlanetNumber
- jupiter :: PlanetNumber
- saturn :: PlanetNumber
- uranus :: PlanetNumber
- neptune :: PlanetNumber
- pluto :: PlanetNumber
- julian :: GregFlag
- meanNode :: PlanetNumber
- gregorian :: GregFlag
- trueNode :: PlanetNumber
- meanApog :: PlanetNumber
- speed :: CalcFlag
- oscuApog :: PlanetNumber
- swissEph :: CalcFlag
- earth :: PlanetNumber
- chiron :: PlanetNumber
- equatorialPositions :: CalcFlag
- useSwissEph :: EpheFlag
- specialEclNut :: PlanetNumber
- useJplEph :: EpheFlag
- useMoshierEph :: EpheFlag
- splitRoundSec :: SplitDegFlag
- splitRoundMin :: SplitDegFlag
- splitRoundDeg :: SplitDegFlag
- splitZodiacal :: SplitDegFlag
- splitNakshatra :: SplitDegFlag
- eclipseCentral :: EclipseFlag
- splitKeepSign :: SplitDegFlag
- splitKeepDeg :: SplitDegFlag
- eclipseNonCentral :: EclipseFlag
- eclipseTotal :: EclipseFlag
- eclipseAnnular :: EclipseFlag
- eclipsePartial :: EclipseFlag
- eclipseAnnularTotal :: EclipseFlag
- eclipseHybrid :: EclipseFlag
- anyEclipse :: EclipseFlag
- eclipsePenumbral :: EclipseFlag
- eclipseSolar :: EclipseFlag
- c_swe_set_ephe_path :: CString -> IO ()
- eclipseLunar :: EclipseFlag
- c_swe_close :: IO ()
- c_swe_julday :: CInt -> CInt -> CInt -> CDouble -> GregFlag -> CDouble
- c_swe_revjul :: CDouble -> GregFlag -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CDouble -> IO ()
- c_swe_calc_ut :: CDouble -> PlanetNumber -> CalcFlag -> Ptr CDouble -> CString -> IO CalcFlag
- c_swe_houses :: CDouble -> CDouble -> CDouble -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt
- c_swe_house_pos :: CDouble -> CDouble -> CDouble -> CInt -> Ptr CDouble -> CString -> IO CDouble
- c_swe_cotrans_sp :: Ptr CDouble -> Ptr CDouble -> CDouble -> IO ()
- c_swe_split_deg :: CDouble -> SplitDegFlag -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CDouble -> Ptr CInt -> IO ()
- c_swe_deltat :: CDouble -> IO CDouble
- c_swe_sidtime :: CDouble -> IO CDouble
- c_swe_sidtime0 :: CDouble -> CDouble -> CDouble -> IO CDouble
- c_swe_deltat_ex :: CDouble -> EpheFlag -> CString -> IO CDouble
- c_swe_utc_to_jd :: CInt -> CInt -> CInt -> CInt -> CInt -> CDouble -> GregFlag -> Ptr CDouble -> CString -> IO CInt
- c_swe_jdet_to_utc :: CDouble -> GregFlag -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CDouble -> IO ()
- c_swe_jdut1_to_utc :: CDouble -> GregFlag -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CDouble -> IO ()
- c_swe_pheno :: CDouble -> PlanetNumber -> CalcFlag -> Ptr CDouble -> CString -> IO CInt
- c_swe_pheno_ut :: CDouble -> PlanetNumber -> CalcFlag -> Ptr CDouble -> CString -> IO CInt
- c_swe_solcross :: CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_solcross_between :: CDouble -> CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_solcross_ut :: CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_solcross_ut_between :: CDouble -> CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_mooncross :: CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_mooncross_between :: CDouble -> CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_mooncross_ut :: CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_mooncross_ut_between :: CDouble -> CDouble -> CDouble -> CalcFlag -> CString -> IO CDouble
- c_swe_mooncross_node :: CDouble -> CalcFlag -> Ptr CDouble -> Ptr CDouble -> CString -> IO CDouble
- c_swe_mooncross_node_ut :: CDouble -> CalcFlag -> Ptr CDouble -> Ptr CDouble -> CString -> IO CDouble
- c_swe_helio_cross :: PlanetNumber -> CDouble -> CDouble -> CalcFlag -> CInt -> Ptr CDouble -> CString -> IO CInt
- c_swe_helio_cross_ut :: PlanetNumber -> CDouble -> CDouble -> CalcFlag -> CInt -> Ptr CDouble -> CString -> IO CInt
- c_swe_sol_eclipse_when_glob :: CDouble -> CalcFlag -> EclipseFlag -> Ptr CDouble -> CInt -> CString -> IO CInt
- c_swe_sol_eclipse_where :: CDouble -> CalcFlag -> Ptr CDouble -> Ptr CDouble -> CString -> IO CInt
- c_swe_sol_eclipse_when_loc :: CDouble -> CalcFlag -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> CInt -> CString -> IO CInt
- c_swe_lun_eclipse_when :: CDouble -> CalcFlag -> EclipseFlag -> Ptr CDouble -> CInt -> CString -> IO CInt
- c_swe_lun_eclipse_when_loc :: CDouble -> CalcFlag -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> CInt -> CString -> IO CInt
Documentation
newtype PlanetNumber Source #
Constructors
| PlanetNumber | |
Fields | |
Instances
| Eq PlanetNumber Source # | |
Defined in Foreign.SwissEphemeris | |
| Show PlanetNumber Source # | |
Defined in Foreign.SwissEphemeris Methods showsPrec :: Int -> PlanetNumber -> ShowS # show :: PlanetNumber -> String # showList :: [PlanetNumber] -> ShowS # | |
| Storable PlanetNumber Source # | |
Defined in Foreign.SwissEphemeris Methods sizeOf :: PlanetNumber -> Int # alignment :: PlanetNumber -> Int # peekElemOff :: Ptr PlanetNumber -> Int -> IO PlanetNumber # pokeElemOff :: Ptr PlanetNumber -> Int -> PlanetNumber -> IO () # peekByteOff :: Ptr b -> Int -> IO PlanetNumber # pokeByteOff :: Ptr b -> Int -> PlanetNumber -> IO () # peek :: Ptr PlanetNumber -> IO PlanetNumber # poke :: Ptr PlanetNumber -> PlanetNumber -> IO () # | |
newtype SplitDegFlag Source #
Constructors
| SplitDegFlag | |
Fields | |
Instances
| Eq SplitDegFlag Source # | |
Defined in Foreign.SwissEphemeris | |
| Show SplitDegFlag Source # | |
Defined in Foreign.SwissEphemeris Methods showsPrec :: Int -> SplitDegFlag -> ShowS # show :: SplitDegFlag -> String # showList :: [SplitDegFlag] -> ShowS # | |
newtype EclipseFlag Source #
Constructors
| EclipseFlag | |
Fields | |
Instances
| Eq EclipseFlag Source # | |
Defined in Foreign.SwissEphemeris | |
| Show EclipseFlag Source # | |
Defined in Foreign.SwissEphemeris Methods showsPrec :: Int -> EclipseFlag -> ShowS # show :: EclipseFlag -> String # showList :: [EclipseFlag] -> ShowS # | |
sun :: PlanetNumber Source #
moon :: PlanetNumber Source #
venus :: PlanetNumber Source #
mars :: PlanetNumber Source #
pluto :: PlanetNumber Source #
earth :: PlanetNumber Source #
c_swe_set_ephe_path :: CString -> IO () Source #
c_swe_close :: IO () Source #
c_swe_revjul :: CDouble -> GregFlag -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CDouble -> IO () Source #
Reverse of c_swe_julday: produce a gregorian date
c_swe_calc_ut :: CDouble -> PlanetNumber -> CalcFlag -> Ptr CDouble -> CString -> IO CalcFlag Source #
Calculate the position of a body, given a time in
Universal Time. Note that this is marginally more expensive than
swe_calc, but I use this one to keep consistency with swe_houses.
c_swe_houses :: CDouble -> CDouble -> CDouble -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #
Get the house cusps and other relevant angles for
a given time and place. Note that there's also a
swe_houses_armc if one happens to have the ARMC
and the ecliptic obliquity handy from other calculations.
c_swe_house_pos :: CDouble -> CDouble -> CDouble -> CInt -> Ptr CDouble -> CString -> IO CDouble Source #
Calculate the house a planet is in. Takes into account obliquity of the ecliptic. Works for all house systems, except Koch.
c_swe_cotrans_sp :: Ptr CDouble -> Ptr CDouble -> CDouble -> IO () Source #
Low-level function to translate between coordinate systems, with speed position included.
c_swe_split_deg :: CDouble -> SplitDegFlag -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CDouble -> Ptr CInt -> IO () Source #
Split a given ecliptic longitude into sign (number) degrees, minutes and seconds.
c_swe_deltat :: CDouble -> IO CDouble Source #
Calculate the delta time for a given julian time,
delta time + julian time = ephemeris time
NOTE: there's also swe_deltat_ex which takes an ephemeris
flag explicitly, vs. the current global value.
my calculations work in one ephemeris, so this one is suitable.
c_swe_sidtime :: CDouble -> IO CDouble Source #
Calculate the sidereal time for a given julian time.
NOTE: there's also swe_sidtime0 which requires obliquity
and nutation, this one computes them internally.
c_swe_sidtime0 :: CDouble -> CDouble -> CDouble -> IO CDouble Source #
Calculate the sidereal time for a given julian time, obliquity and nutation.
Arguments
| :: CDouble | JulianTime, in a UT scale. |
| -> EpheFlag | Ephemeris to use (for tidal acceleration data) |
| -> CString | For warning/error message |
| -> IO CDouble | Delta T, if the correct ephemeris is being used. |
Same as c_swe_deltat, but expects one to have explicitly
selected an ephemeris mode, and returns a warning if not.
Arguments
| :: CInt | year |
| -> CInt | month |
| -> CInt | day |
| -> CInt | hour |
| -> CInt | min |
| -> CDouble | sec |
| -> GregFlag | gregorian/julian |
| -> Ptr CDouble |
|
| -> CString | error string |
| -> IO CInt |
Given a Universal Time input (UTC, but it's considered to be UT1 if before 1971, or if the leap is too great.)
c_swe_sol_eclipse_when_loc Source #
Arguments
| :: CDouble | JD(UT), time to start searching |
| -> CalcFlag | iflag |
| -> Ptr CDouble | geopos of a known locale |
| -> Ptr CDouble |
|
| -> Ptr CDouble |
|
| -> CInt | BOOL: search backward? |
| -> CString | serr |
| -> IO CInt | ret (ERR/eclipse type) |
Given a search date, latlngheight of a geographic vantage point, return an eclipse's maximum, four contacts and other important events, and various attributes. See: 8.2. swe_sol_eclipse_when_loc. NOTE(luis) only providing the C binding right now, as I have no current use for all this data, and don't want to provide an opinionated Haskell equivalent until I do.
c_swe_lun_eclipse_when_loc Source #
Arguments
| :: CDouble | JD(UT), time to start searching |
| -> CalcFlag | iflag |
| -> Ptr CDouble | geopos of a known locale |
| -> Ptr CDouble |
|
| -> Ptr CDouble |
|
| -> CInt | BOOL: search backward? |
| -> CString | serr |
| -> IO CInt | ret (ERR/eclipse type) |
Given a search date, latlngheight of a geographic vantage point, return an eclipse's maximum, four contacts and other important events, and various attributes. See: 8.9. swe_lun_eclipse_when_loc. NOTE(luis) only providing the C binding right now, as I have no current use for all this data, and don't want to provide an opinionated Haskell equivalent until I do.