{-# LANGUAGE DeriveGeneric #-}
module SwissEphemeris (
Planet(..)
, HouseSystem(..)
, JulianTime
, Coordinates(..)
, HouseCusps(..)
, Angles(..)
, CuspsCalculation(..)
, defaultCoordinates
, mkCoordinates
, julianDay
, setEphemeridesPath
, setNoEphemeridesPath
, closeEphemerides
, withEphemerides
, withoutEphemerides
, calculateCoordinates
, calculateCusps
, calculateCuspsLenient
, calculateCuspsStrict
)where
import Foreign.SwissEphemeris
import Foreign
import GHC.Generics
import Foreign.C.Types
import Foreign.C.String
import Data.Char ( ord )
import Control.Exception (bracket_)
data Planet = Sun
| Moon
| Mercury
| Venus
| Mars
| Jupiter
| Saturn
| Uranus
| Neptune
| Pluto
| MeanNode
| TrueNode
| MeanApog
| OscuApog
| Earth
| Chiron
deriving (Show, Eq, Ord, Enum, Generic)
data HouseSystem = Placidus
| Koch
| Porphyrius
| Regiomontanus
| Campanus
| Equal
| WholeSign
deriving (Show, Eq, Ord, Enum, Generic)
type JulianTime = Double
data Coordinates = Coordinates
{
lng :: Double
, lat :: Double
, distance :: Double
, lngSpeed :: Double
, latSpeed :: Double
, distSpeed :: Double
} deriving (Show, Eq, Ord, Generic)
defaultCoordinates :: Coordinates
defaultCoordinates = Coordinates 0 0 0 0 0 0
mkCoordinates :: Coordinates
mkCoordinates = defaultCoordinates
data HouseCusps = HouseCusps
{
i :: Double
, ii :: Double
, iii :: Double
, iv :: Double
, v :: Double
, vi :: Double
, vii :: Double
, viii :: Double
, ix :: Double
, x :: Double
, xi :: Double
, xii :: Double
} deriving (Show, Eq, Generic)
data Angles = Angles
{
ascendant :: Double
, mc :: Double
, armc :: Double
, vertex :: Double
, equatorialAscendant :: Double
, coAscendantKoch :: Double
, coAscendantMunkasey :: Double
, polarAscendant :: Double
} deriving (Show, Eq, Generic)
data CuspsCalculation = CuspsCalculation
{
houseCusps :: HouseCusps
, angles :: Angles
, systemUsed :: HouseSystem
} deriving (Show, Eq, Generic)
toHouseSystemFlag :: HouseSystem -> Int
toHouseSystemFlag Placidus = ord 'P'
toHouseSystemFlag Koch = ord 'K'
toHouseSystemFlag Porphyrius = ord 'O'
toHouseSystemFlag Regiomontanus = ord 'R'
toHouseSystemFlag Campanus = ord 'C'
toHouseSystemFlag Equal = ord 'A'
toHouseSystemFlag WholeSign = ord 'W'
fromList :: [Double] -> Coordinates
fromList (sLng : sLat : c : d : e : f : _) = Coordinates sLng sLat c d e f
fromList _ = error "Invalid coordinate array"
fromCuspsList :: [Double] -> HouseCusps
fromCuspsList (_ : _i : _ii : _iii : _iv : _v : _vi : _vii : _viii : _ix : _x : _xi : _xii : _)
= HouseCusps _i _ii _iii _iv _v _vi _vii _viii _ix _x _xi _xii
fromCuspsList _ = error "Invalid cusps list"
fromAnglesList :: [Double] -> Angles
fromAnglesList (a : _mc : _armc : vtx : ea : cak : cam : pa : _ : _) =
Angles a _mc _armc vtx ea cak cam pa
fromAnglesList _ = error "Invalid angles list"
planetNumber :: Planet -> PlanetNumber
planetNumber p = PlanetNumber $ CInt y
where
y = fromIntegral $ fromEnum p :: Int32
setEphemeridesPath :: FilePath -> IO ()
setEphemeridesPath path =
withCString path $ \ephePath -> c_swe_set_ephe_path ephePath
setNoEphemeridesPath :: IO ()
setNoEphemeridesPath = c_swe_set_ephe_path nullPtr
closeEphemerides :: IO ()
closeEphemerides = c_swe_close
withEphemerides :: FilePath -> (IO a) -> IO a
withEphemerides ephemeridesPath =
bracket_ (setEphemeridesPath ephemeridesPath)
(closeEphemerides)
withoutEphemerides :: (IO a) -> IO a
withoutEphemerides =
bracket_ (setNoEphemeridesPath)
(closeEphemerides)
julianDay :: Int -> Int -> Int -> Double -> JulianTime
julianDay year month day hour = realToFrac $ c_swe_julday y m d h gregorian
where
y = fromIntegral year
m = fromIntegral month
d = fromIntegral day
h = realToFrac hour
calculateCoordinates :: JulianTime -> Planet -> IO (Either String Coordinates)
calculateCoordinates time planet =
allocaArray 6 $ \coords -> allocaArray 256 $ \errorP -> do
iflgret <- c_swe_calc (realToFrac time)
(planetNumber planet)
speed
coords
errorP
if unCalcFlag iflgret < 0
then do
msg <- peekCAString errorP
return $ Left msg
else do
result <- peekArray 6 coords
return $ Right $ fromList $ map realToFrac result
calculateCusps :: JulianTime -> Coordinates -> HouseSystem -> IO CuspsCalculation
calculateCusps = calculateCuspsLenient
calculateCuspsLenient :: JulianTime -> Coordinates -> HouseSystem -> IO CuspsCalculation
calculateCuspsLenient time loc sys = allocaArray 13 $ \cusps ->
allocaArray 10 $ \ascmc -> do
rval <- c_swe_houses (realToFrac time)
(realToFrac $ lat loc)
(realToFrac $ lng loc)
(fromIntegral $ toHouseSystemFlag sys)
cusps
ascmc
cuspsL <- peekArray 13 cusps
anglesL <- peekArray 10 ascmc
return $ CuspsCalculation
(fromCuspsList $ map realToFrac $ cuspsL)
(fromAnglesList $ map realToFrac $ anglesL)
(if rval < 0 then Porphyrius else sys)
calculateCuspsStrict :: JulianTime -> Coordinates -> HouseSystem -> IO (Either String CuspsCalculation)
calculateCuspsStrict time loc sys = do
calcs@(CuspsCalculation _ _ sys') <- calculateCuspsLenient time loc sys
if sys' /= sys then
pure $ Left $ "Unable to calculate cusps in the requested house system (used " ++ (show sys') ++ " instead.)"
else
pure $ Right calcs