Skip to content

Commit

Permalink
Merge pull request #17 from lfborjas/options-for-split
Browse files Browse the repository at this point in the history
Exposes more constructors, take options for `splitDegrees`, Nakshatras.
  • Loading branch information
lfborjas authored Sep 15, 2020
2 parents 3388e85 + 51715a8 commit 06287a8
Show file tree
Hide file tree
Showing 7 changed files with 125 additions and 34 deletions.
12 changes: 12 additions & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,17 @@
# Changelog for swiss-ephemeris

## v1.2.0.0 (2020-09-14)

**BREAKING CHANGE:** `splitDegrees` now takes options that reflect the options in the underlying library.

* Constructors for `JulianTime` and `SiderealTime` are now exposed.
* Introduce `SplitDegreesOption` enum for all options one can split degrees with; amends `splitDegrees` to take
said options as the first argument.
* `splitDegreesZodiac` is unchanged, though a mere veneer for the now more powerful `splitDegrees`.
* Since `splitDegreesZodiac` goes the extra enum-mile to provide human-readable zodiac names, and the underlying
library can also split on Nakshatras, we now include the `NakshatraName` enum. Names are from wikipedia
and I saw some variants, so please forgive any mispellings!

## v1.1.0.0 (2020-09-12)

**BREAKING CHANGE:** the `Coordinates` type has been retired, in favor of the more specific
Expand Down
2 changes: 2 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ Haskell bindings for the [Swiss Ephemeris](https://www.astro.com/swisseph/swephi

See the tests in the `spec` folder for thorough example usage, but here's a simple "main" that demonstrates the current abilities, inspired by the [sample program in the official library](https://www.astro.com/swisseph/swephprg.htm#_Toc46406771):

**NOTE:** this library is under very active development, as such, most releases in v1.x will probably show a fastly evolving API, which is reflected by the fact that new versions have been increasing the major version numbers (in [PVP](https://pvp.haskell.org/), unlike semver, the first _two_ components of the version correspond to the major version.)

```haskell
import SwissEphemeris

Expand Down
2 changes: 1 addition & 1 deletion package.yaml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: swiss-ephemeris
version: 1.1.0.0
version: 1.2.0.0
github: "lfborjas/swiss-ephemeris"
license: GPL-2
author: "Luis Borjas Reyes"
Expand Down
50 changes: 33 additions & 17 deletions src/SwissEphemeris.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,14 +17,16 @@
-- There's a wealth of other calculations possible with the underlying library, however,
-- please refer to their documentation and the bundled sources for ideas!
module SwissEphemeris
( -- newtypes without exposed constructors
JulianTime,
SiderealTime,
( -- fundamental aliases/newtypes
JulianTime (..),
SiderealTime (..),
HouseCusp,
-- fundamental enumerations
SplitDegreesOption (..),
Planet (..),
HouseSystem (..),
ZodiacSignName (..),
NakshatraName (..),
-- coordinate/position systems
EclipticPosition (..),
EquatorialPosition (..),
Expand Down Expand Up @@ -60,12 +62,14 @@ module SwissEphemeris
julianDay,
deltaTime,
-- utilities for angles:
defaultSplitDegreesOptions,
splitDegrees,
splitDegreesZodiac,
)
where

import Control.Exception (bracket_)
import Data.Semigroup ((<>))
import Foreign
import Foreign.C.String
import Foreign.SwissEphemeris
Expand Down Expand Up @@ -256,8 +260,8 @@ calculateHousePositionSimple sys time loc pos = do
case obliquityAndNutation of
Left e -> return $ Left e
Right on -> do
siderealTime <- calculateSiderealTime time on
let armc' = (unSidereal $ siderealTime) * 15 + geoLng loc
SiderealTime siderealTime <- calculateSiderealTime time on
let armc' = siderealTime * 15 + geoLng loc
calculateHousePosition sys armc' loc on pos

-- | If you happen to have the correct ARMC for a time and place (obtained from calculateCusps)
Expand Down Expand Up @@ -315,27 +319,39 @@ deltaTime jt = do
return $ realToFrac deltaT

-- | Given a longitude, return the degrees it's from its nearest sign,
-- minutes, seconds and seconds fraction.
-- minutes, and seconds; with seconds rounded. Convenience alias for `splitDegrees`,
-- when wanting to display e.g. a table in a horoscope.
splitDegreesZodiac :: Double -> LongitudeComponents
splitDegreesZodiac d =
LongitudeComponents (Just $ toEnum z) deg m s sf
where
(z, deg, m, s, sf) = splitDegrees' options d
options = mkSplitDegOptions $ defaultSplitDegOptions ++ [splitZodiacal]
splitDegreesZodiac = splitDegrees $ defaultSplitDegreesOptions <> [SplitZodiacal, RoundSeconds]

-- | Given a longitude, return the degrees from zero, minutes, seconds and seconds fraction.
splitDegrees :: Double -> LongitudeComponents
splitDegrees d =
LongitudeComponents Nothing deg m s sf
-- | Given a `Double` representing an ecliptic longitude, split it according to any
-- options from `SplitDegreesOption`:
-- if `SplitZodiacal` or `SplitNakshatra` are specified, they're returned
-- in `longitudeZodiacSign` and `longitudeNakshatra`, respectively.
-- If neither of those is specified, the raw `signum` is then populated, in
-- `longitudeSignum` (-1 for negative, 1, for positive.)
-- /NOTE:/ this function can also be used for latitudes, speeds or quantities
-- from other positional systems (like declinations,) but the zodiacal or
-- nakshatra components would of course be nonsensical.
splitDegrees :: [SplitDegreesOption] -> Double -> LongitudeComponents
splitDegrees options d =
LongitudeComponents sign deg m s sf signum' nak
where
(_, deg, m, s, sf) = splitDegrees' options d
options = mkSplitDegOptions $ defaultSplitDegOptions
(z, deg, m, s, sf) = splitDegrees' flags d
flags = foldSplitDegOptions $ map splitOptionToFlag options
isZodiacSplit = SplitZodiacal `elem` options
isNakshatraSplit = SplitNakshatra `elem` options
sign = if isZodiacSplit then (Just . toEnum $ z) else Nothing
nak = if isNakshatraSplit then (Just . toEnum $ z) else Nothing
signum' = if (not isZodiacSplit && not isNakshatraSplit) then Just z else Nothing

-- | Internal implementation to split a given longitude into components.
splitDegrees' :: SplitDegFlag -> Double -> (Int, Integer, Integer, Integer, Double)
splitDegrees' options deg =
unsafePerformIO $ do
alloca $ \ideg -> alloca $ \imin -> alloca $ \isec -> alloca $ \dsecfr -> alloca $ \isign -> do
-- initialize with 0, since it may never be touched.
poke dsecfr 0
_ <-
c_swe_split_deg
(realToFrac deg)
Expand Down
80 changes: 71 additions & 9 deletions src/SwissEphemeris/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,58 @@ data ZodiacSignName
| Pisces
deriving (Eq, Show, Enum, Generic)

-- | 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.
data NakshatraName
= Ashvini
| Bharani
| Krittika
| Rohini
| Mrigashirsha
| Ardra
| Punarvasu
| Pushya
| Ashlesha
| Magha
| PurvaPhalghuni
| UttaraPhalguni
| Hasta
| Chitra
| Swati
| Vishakha
| Anuradha
| Jyeshtha
| Mula
| PurvaAshadha
| UttaraAshadha
| Sravana
| Dhanishta
| Shatabhisha
| PurvaBhadrapada
| UttaraBhadrapada
| Revati
deriving (Eq, Show, Enum, Generic)

-- | 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.
data SplitDegreesOption
= RoundSeconds
| RoundMinutes
| RoundDegrees
| SplitZodiacal
| SplitNakshatra
| KeepSign
| KeepDegrees
deriving (Eq, Show, Enum, Generic)

-- | Represents an instant in Julian time.
-- see:
-- <https://www.astro.com/swisseph/swephprg.htm#_Toc49847871 8. Date and time conversion functions>
Expand All @@ -78,7 +130,7 @@ newtype JulianTime = JulianTime {unJulianTime :: Double}
deriving (Show, Eq, Ord)

-- | Represents an instant in sidereal time
newtype SiderealTime = SiderealTime {unSidereal :: Double}
newtype SiderealTime = SiderealTime {unSiderealTime :: Double}
deriving (Show, Eq, Ord)

-- | The cusp of a given "house" or "sector". It is an ecliptic longitude.
Expand Down Expand Up @@ -168,7 +220,9 @@ data LongitudeComponents = LongitudeComponents
longitudeDegrees :: Integer,
longitudeMinutes :: Integer,
longitudeSeconds :: Integer,
longitudeSecondsFraction :: Double
longitudeSecondsFraction :: Double,
longitudeSignum :: Maybe Int,
longitudeNakshatra :: Maybe NakshatraName
}
deriving (Show, Eq, Generic)

Expand All @@ -180,14 +234,22 @@ mkCalculationOptions = CalcFlag . foldr ((.|.) . unCalcFlag) 0
defaultCalculationOptions :: [CalcFlag]
defaultCalculationOptions = [speed, swissEph]

mkSplitDegOptions :: [SplitDegFlag] -> SplitDegFlag
mkSplitDegOptions = SplitDegFlag . foldr ((.|.) . unSplitDegFlag) 0
foldSplitDegOptions :: [SplitDegFlag] -> SplitDegFlag
foldSplitDegOptions = SplitDegFlag . foldr ((.|.) . unSplitDegFlag) 0

splitOptionToFlag :: SplitDegreesOption -> SplitDegFlag
splitOptionToFlag RoundSeconds = splitRoundSec
splitOptionToFlag RoundMinutes = splitRoundMin
splitOptionToFlag RoundDegrees = splitRoundDeg
splitOptionToFlag SplitZodiacal = splitZodiacal
splitOptionToFlag SplitNakshatra = splitNakshatra
splitOptionToFlag KeepSign = splitKeepSign
splitOptionToFlag KeepDegrees = splitKeepDeg

defaultSplitDegOptions :: [SplitDegFlag]
defaultSplitDegOptions =
[ splitKeepDeg, -- don't round up to the next degree
splitKeepSign -- don't round up to the next sign
]
-- | Convenient defaults when using `splitDegrees`:
-- Omit rounding if it would bring it over the next sign or degree.
defaultSplitDegreesOptions :: [SplitDegreesOption]
defaultSplitDegreesOptions = [KeepSign, KeepDegrees]

-- Helpers

Expand Down
4 changes: 2 additions & 2 deletions swiss-ephemeris.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,10 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 25f7b59663125c750ee70fd238ed152f8c7496541d173c1e07bcb3944b332ee1
-- hash: e7dc9c3e02181a082342d7937373cda9b8b1506c04be5e776bed3635ada3df69

name: swiss-ephemeris
version: 1.1.0.0
version: 1.2.0.0
synopsis: Haskell bindings for the Swiss Ephemeris C library
description: Please see the README on GitHub at <https://github.com/lfborjas/swiss-ephemeris#readme>
category: Data, Astrology
Expand Down
9 changes: 4 additions & 5 deletions test/SwissEphemerisSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ module SwissEphemerisSpec (spec) where
import Control.Monad (forM_)
import Data.Either (isLeft, isRight)
import SwissEphemeris
import SwissEphemeris.Internal (JulianTime (..))
import Test.Hspec
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck
Expand Down Expand Up @@ -39,13 +38,13 @@ spec = do
describe "splitDegrees" $ do
it "splits a given longitude into its components, not relative to the zodiac" $ do
let longitude = 285.64723120365153
split = LongitudeComponents {longitudeZodiacSign = Nothing, longitudeDegrees = 285, longitudeMinutes = 38, longitudeSeconds = 50, longitudeSecondsFraction = 3.233314550481481e-2}
(splitDegrees longitude) `shouldBe` split
split = LongitudeComponents {longitudeZodiacSign = Nothing, longitudeDegrees = 285, longitudeMinutes = 38, longitudeSeconds = 50, longitudeSecondsFraction = 3.233314550481481e-2, longitudeSignum = Just 1, longitudeNakshatra = Nothing}
(splitDegrees defaultSplitDegreesOptions longitude) `shouldBe` split

describe "splitDegreesZodiac" $ do
it "splits a given longitude into its components, relative to the nearest zodiac sign" $ do
it "splits a given longitude into its components, relative to the nearest zodiac sign; rounds seconds, keeps degrees and sign." $ do
let longitude = 285.64723120365153
split = LongitudeComponents {longitudeZodiacSign = Just Capricorn, longitudeDegrees = 15, longitudeMinutes = 38, longitudeSeconds = 50, longitudeSecondsFraction = 3.233314550481481e-2}
split = LongitudeComponents {longitudeZodiacSign = Just Capricorn, longitudeDegrees = 15, longitudeMinutes = 38, longitudeSeconds = 50, longitudeSecondsFraction = 0.0, longitudeSignum = Nothing, longitudeNakshatra = Nothing}
(splitDegreesZodiac longitude) `shouldBe` split

around_ (withoutEphemerides) $ do
Expand Down

0 comments on commit 06287a8

Please sign in to comment.