Safe Haskell | None |
---|---|
Language | Haskell2010 |
The types defined here are exported publicly for convenience, but at least in versions <= 2.x, they're likely to evolve.
Synopsis
- class Eq a => HasEclipticLongitude a where
- getEclipticLongitude :: a -> Double
- setEclipticLongitude :: a -> Double -> a
- data Planet
- data HouseSystem
- data ZodiacSignName
- data NakshatraName
- data SplitDegreesOption
- data CalendarOption
- data EphemerisOption
- data EventSearchDirection
- data SolarEclipseType
- data LunarEclipseType
- data PlanetMotion
- data LunarPhaseName
- type HouseCusp = Double
- data EclipticPosition = EclipticPosition {}
- data GeographicPosition = GeographicPosition {}
- data EquatorialPosition = EquatorialPosition {}
- data ObliquityInformation = ObliquityInformation {}
- data HousePosition = HousePosition {}
- data Angles = Angles {}
- data CuspsCalculation = CuspsCalculation {
- houseCusps :: [HouseCusp]
- angles :: Angles
- systemUsed :: HouseSystem
- data LongitudeComponents = LongitudeComponents {}
- data PlanetPhenomenon = PlanetPhenomenon {}
- mkCalculationOptions :: [CalcFlag] -> CalcFlag
- defaultCalculationOptions :: [CalcFlag]
- defaultCalculationFlag :: CalcFlag
- foldSplitDegOptions :: [SplitDegFlag] -> SplitDegFlag
- splitOptionToFlag :: SplitDegreesOption -> SplitDegFlag
- defaultSplitDegreesOptions :: [SplitDegreesOption]
- solarEclipseTypeToFlag :: SolarEclipseType -> EclipseFlag
- lunarEclipseTypeToFlag :: LunarEclipseType -> EclipseFlag
- eclipseFlagToTypeSolar :: EclipseFlag -> Maybe SolarEclipseType
- eclipseFlagToTypeLunar :: EclipseFlag -> Maybe LunarEclipseType
- match :: EclipseFlag -> EclipseFlag -> Bool
- foldEclipseOptions :: [EclipseFlag] -> EclipseFlag
- defaultEclipseFlag :: EclipseFlag
- totalSolarEclipseFlag :: EclipseFlag
- annularSolarEclipseFlag :: EclipseFlag
- hybridSolarEclipseFlag :: EclipseFlag
- partialSolarEclipseFlag :: EclipseFlag
- totalLunarEclipseFlag :: EclipseFlag
- partialLunarEclipseFlag :: EclipseFlag
- penumbralLunarEclipseFlag :: EclipseFlag
- toHouseSystemFlag :: HouseSystem -> Int
- coordinatesFromList :: [Double] -> EclipticPosition
- eclipticFromList :: [Double] -> EclipticPosition
- eclipticToList :: EclipticPosition -> [Double]
- equatorialFromList :: [Double] -> EquatorialPosition
- equatorialToList :: EquatorialPosition -> [Double]
- obliquityNutationFromList :: [Double] -> ObliquityInformation
- anglesFromList :: [Double] -> Angles
- planetNumber :: Planet -> PlanetNumber
- numberToPlanet :: PlanetNumber -> Planet
- allocaErrorMessage :: (Ptr CChar -> IO b) -> IO b
- calendarOptionToFlag :: CalendarOption -> GregFlag
- ephemerisOptionToFlag :: EphemerisOption -> EpheFlag
- moonPhaseToAngle :: LunarPhaseName -> Double
Documentation
class Eq a => HasEclipticLongitude a where Source #
For objects that can be placed along the ecliptic in a 1-dimensional "longitude-only" manner.
getEclipticLongitude :: a -> Double Source #
setEclipticLongitude :: a -> Double -> a Source #
Instances
HasEclipticLongitude EclipticPosition Source # | |
Defined in SwissEphemeris.Internal | |
(Real a, Eq a, Fractional a) => HasEclipticLongitude (EphemerisPosition a) Source # | |
Defined in SwissEphemeris.Precalculated getEclipticLongitude :: EphemerisPosition a -> Double Source # setEclipticLongitude :: EphemerisPosition a -> Double -> EphemerisPosition a 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
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 NakshatraName Source #
Nakshatras, provided for thoroughness, please excuse any misspellings! List from: https://en.wikipedia.org/wiki/List_of_Nakshatras note that the underlying library uses 27 nakshatras, so Abhijit is omitted.
Instances
data SplitDegreesOption Source #
Options to split a Double
representing degrees:
RoundSeconds -- round at the seconds granularity (omits seconds fraction.)
RoundMinutes -- round at the minutes granularity.
RoundDegrees -- round at the degrees granularity.
SplitZodiacal -- relative to zodiac signs.
SplitNakshatra -- relative to nakshatra.
KeepSign -- when rounding, don't round if it'll move it to the next zodiac/nakshatra sector.
KeepDegrees -- when rounding, don't round if it'll move it to the next degree.
Instances
data CalendarOption Source #
Calendar options
Instances
Eq CalendarOption Source # | |
Defined in SwissEphemeris.Internal (==) :: CalendarOption -> CalendarOption -> Bool # (/=) :: CalendarOption -> CalendarOption -> Bool # | |
Show CalendarOption Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> CalendarOption -> ShowS # show :: CalendarOption -> String # showList :: [CalendarOption] -> ShowS # |
data EphemerisOption Source #
Instances
Eq EphemerisOption Source # | |
Defined in SwissEphemeris.Internal (==) :: EphemerisOption -> EphemerisOption -> Bool # (/=) :: EphemerisOption -> EphemerisOption -> Bool # | |
Show EphemerisOption Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> EphemerisOption -> ShowS # show :: EphemerisOption -> String # showList :: [EphemerisOption] -> ShowS # |
data EventSearchDirection Source #
When looking for eclipses, occulations or crossings, determine the temporal direction to take from the provided start time.
Instances
Eq EventSearchDirection Source # | |
Defined in SwissEphemeris.Internal (==) :: EventSearchDirection -> EventSearchDirection -> Bool # (/=) :: EventSearchDirection -> EventSearchDirection -> Bool # | |
Show EventSearchDirection Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> EventSearchDirection -> ShowS # show :: EventSearchDirection -> String # showList :: [EventSearchDirection] -> ShowS # |
data SolarEclipseType Source #
All possible types of solar eclipses.
Instances
Eq SolarEclipseType Source # | |
Defined in SwissEphemeris.Internal (==) :: SolarEclipseType -> SolarEclipseType -> Bool # (/=) :: SolarEclipseType -> SolarEclipseType -> Bool # | |
Show SolarEclipseType Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> SolarEclipseType -> ShowS # show :: SolarEclipseType -> String # showList :: [SolarEclipseType] -> ShowS # |
data LunarEclipseType Source #
All possible types of lunar eclipses.
Instances
Eq LunarEclipseType Source # | |
Defined in SwissEphemeris.Internal (==) :: LunarEclipseType -> LunarEclipseType -> Bool # (/=) :: LunarEclipseType -> LunarEclipseType -> Bool # | |
Show LunarEclipseType Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> LunarEclipseType -> ShowS # show :: LunarEclipseType -> String # showList :: [LunarEclipseType] -> ShowS # |
data PlanetMotion Source #
Apparent motion of a planet, from a geocentric observation.
Instances
Eq PlanetMotion Source # | |
Defined in SwissEphemeris.Internal (==) :: PlanetMotion -> PlanetMotion -> Bool # (/=) :: PlanetMotion -> PlanetMotion -> Bool # | |
Show PlanetMotion Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> PlanetMotion -> ShowS # show :: PlanetMotion -> String # showList :: [PlanetMotion] -> ShowS # |
data LunarPhaseName Source #
Traditional western moon phases.
Instances
Eq LunarPhaseName Source # | |
Defined in SwissEphemeris.Internal (==) :: LunarPhaseName -> LunarPhaseName -> Bool # (/=) :: LunarPhaseName -> LunarPhaseName -> Bool # | |
Ord LunarPhaseName Source # | |
Defined in SwissEphemeris.Internal compare :: LunarPhaseName -> LunarPhaseName -> Ordering # (<) :: LunarPhaseName -> LunarPhaseName -> Bool # (<=) :: LunarPhaseName -> LunarPhaseName -> Bool # (>) :: LunarPhaseName -> LunarPhaseName -> Bool # (>=) :: LunarPhaseName -> LunarPhaseName -> Bool # max :: LunarPhaseName -> LunarPhaseName -> LunarPhaseName # min :: LunarPhaseName -> LunarPhaseName -> LunarPhaseName # | |
Show LunarPhaseName Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> LunarPhaseName -> ShowS # show :: LunarPhaseName -> String # showList :: [LunarPhaseName] -> 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
data EclipticPosition Source #
Position data for a celestial body on the ecliptic, includes rotational speeds. see: 3.4 Position and speed
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 EquatorialPosition Source #
Represents a position on the celestial sphere, with speed information included.
EquatorialPosition | |
|
Instances
data ObliquityInformation Source #
Includes the obliquity of the ecliptic, the Nutation as longitude as well as mean values.
Instances
data HousePosition Source #
The house a celestial body is in.
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
data PlanetPhenomenon Source #
A Planet's "phenomena" record
Instances
Eq PlanetPhenomenon Source # | |
Defined in SwissEphemeris.Internal (==) :: PlanetPhenomenon -> PlanetPhenomenon -> Bool # (/=) :: PlanetPhenomenon -> PlanetPhenomenon -> Bool # | |
Show PlanetPhenomenon Source # | |
Defined in SwissEphemeris.Internal showsPrec :: Int -> PlanetPhenomenon -> ShowS # show :: PlanetPhenomenon -> String # showList :: [PlanetPhenomenon] -> ShowS # |
mkCalculationOptions :: [CalcFlag] -> CalcFlag Source #
defaultSplitDegreesOptions :: [SplitDegreesOption] Source #
Convenient defaults when using splitDegrees
:
Omit rounding if it would bring it over the next sign or degree.
match :: EclipseFlag -> EclipseFlag -> Bool Source #
Equivalent to flag & FLAG_VALUE
in C.
foldEclipseOptions :: [EclipseFlag] -> EclipseFlag Source #
toHouseSystemFlag :: HouseSystem -> Int Source #
coordinatesFromList :: [Double] -> EclipticPosition Source #
eclipticFromList :: [Double] -> EclipticPosition Source #
eclipticToList :: EclipticPosition -> [Double] Source #
equatorialToList :: EquatorialPosition -> [Double] Source #
anglesFromList :: [Double] -> Angles Source #
planetNumber :: Planet -> PlanetNumber Source #
numberToPlanet :: PlanetNumber -> Planet Source #
allocaErrorMessage :: (Ptr CChar -> IO b) -> IO b Source #
As per the programmers manual, error output strings
should accommodate at most 256 characters:
see sweodef.h#266
and the manual:
https://www.astro.com/swisseph/swephprg.htm
in e.g.