module Naqsha.Geometry.Angle
( Angle
, degree , minute, second
, radian
, toDegree, toRadian
, Angular(..)
) where
import Control.Monad ( liftM )
import Data.Default
import Data.Group
import Data.Int
import GHC.Real
import Data.Vector.Unboxed ( MVector(..), Vector, Unbox)
import qualified Data.Vector.Generic as GV
import qualified Data.Vector.Generic.Mutable as GVM
newtype Angle = Angle {unAngle :: Int64} deriving (Enum, Eq, Ord, Unbox, Show, Read)
degree :: Rational -> Angle
degree = Angle . fromInteger . round . (*scale)
where scale = (2^(64:: Int)) % 360
minute :: Rational -> Angle
minute = degree . (*scale)
where scale = 1 % 60
second :: Rational -> Angle
second = degree . (*scale)
where scale = 1 % 3600
radian :: Double -> Angle
radian = Angle . round . (*scale)
where scale = (2^(63:: Int)) / pi
toDegree :: Fractional r => Angle -> r
toDegree = fromRational . (*conv) . toRational . unAngle
where conv = 360 % (2^(64 :: Int))
toRadian :: Angle -> Double
toRadian = (*conv) . fromIntegral . unAngle
where conv = pi / (2^(63:: Int))
instance Default Angle where
def = Angle 0
instance Angular Angle where
toAngle = id
instance Monoid Angle where
mempty = Angle 0
mappend (Angle x) (Angle y) = Angle $ x + y
mconcat = Angle . sum . map unAngle
instance Group Angle where
invert (Angle x) = Angle $ negate x
instance Bounded Angle where
maxBound = Angle maxBound
minBound = Angle minBound
class Angular a where
toAngle :: a -> Angle
newtype instance MVector s Angle = MAngV (MVector s Int64)
newtype instance Vector Angle = AngV (Vector Int64)
instance GVM.MVector MVector Angle where
basicLength (MAngV v) = GVM.basicLength v
basicUnsafeSlice i n (MAngV v) = MAngV $ GVM.basicUnsafeSlice i n v
basicOverlaps (MAngV v1) (MAngV v2) = GVM.basicOverlaps v1 v2
basicUnsafeRead (MAngV v) i = Angle `liftM` GVM.basicUnsafeRead v i
basicUnsafeWrite (MAngV v) i (Angle x) = GVM.basicUnsafeWrite v i x
basicClear (MAngV v) = GVM.basicClear v
basicSet (MAngV v) (Angle x) = GVM.basicSet v x
basicUnsafeNew n = MAngV `liftM` GVM.basicUnsafeNew n
basicUnsafeReplicate n (Angle x) = MAngV `liftM` GVM.basicUnsafeReplicate n x
basicUnsafeCopy (MAngV v1) (MAngV v2) = GVM.basicUnsafeCopy v1 v2
basicUnsafeGrow (MAngV v) n = MAngV `liftM` GVM.basicUnsafeGrow v n
#if MIN_VERSION_vector(0,11,0)
basicInitialize (MAngV v) = GVM.basicInitialize v
#endif
instance GV.Vector Vector Angle where
basicUnsafeFreeze (MAngV v) = AngV `liftM` GV.basicUnsafeFreeze v
basicUnsafeThaw (AngV v) = MAngV `liftM` GV.basicUnsafeThaw v
basicLength (AngV v) = GV.basicLength v
basicUnsafeSlice i n (AngV v) = AngV $ GV.basicUnsafeSlice i n v
basicUnsafeIndexM (AngV v) i = Angle `liftM` GV.basicUnsafeIndexM v i
basicUnsafeCopy (MAngV mv) (AngV v) = GV.basicUnsafeCopy mv v
elemseq _ (Angle x) = GV.elemseq (undefined :: Vector a) x