module Naqsha.Geometry.Internal
( Angle(..)
, degree , minute, second
, radian
, toDegree, toRadian
, Latitude(..), Longitude(..), lat, lon
) where
import Control.Monad ( liftM )
import Data.Bits ( Bits )
import Data.Fixed
import Data.Group
import Data.Int
import Data.Monoid
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
import Text.Read
newtype Angle = Angle {unAngle :: Int64} deriving (Enum, Eq, Ord, Unbox, Show, Read, Bits)
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
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))
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
newtype Latitude = Latitude { unLat :: Angle } deriving (Eq, Ord, Bits)
instance Show Latitude where
show = show . (toDegree :: Angle -> Nano) . unLat
instance Read Latitude where
readPrec = conv <$> readPrec
where conv = lat . degree . (toRational :: Nano -> Rational)
instance Bounded Latitude where
maxBound = lat $ degree 90
minBound = lat $ degree (90)
lat :: Angle -> Latitude
lat = Latitude . normLat
normLat :: Angle -> Angle
normLat ang | degree (90) <= ang && ang < degree 90 = ang
| ang > degree 90 = succ (maxBound <> invert ang)
| otherwise = minBound <> invert ang
newtype Longitude = Longitude { unLong :: Angle }
deriving (Eq, Bounded, Ord, Monoid, Group, Bits)
lon :: Angle -> Longitude
lon = Longitude
instance Show Longitude where
show = show . (toDegree :: Angle -> Nano) . unLong
instance Read Longitude where
readPrec = conv <$> readPrec
where conv = lon . degree . (toRational :: Nano -> Rational)
newtype instance MVector s Latitude = MLatV (MVector s Angle)
newtype instance Vector Latitude = LatV (Vector Angle)
newtype instance MVector s Longitude = MLongV (MVector s Angle)
newtype instance Vector Longitude = LongV (Vector Angle)
instance GVM.MVector MVector Latitude where
basicLength (MLatV v) = GVM.basicLength v
basicUnsafeSlice i n (MLatV v) = MLatV $ GVM.basicUnsafeSlice i n v
basicOverlaps (MLatV v1) (MLatV v2) = GVM.basicOverlaps v1 v2
basicUnsafeRead (MLatV v) i = Latitude `liftM` GVM.basicUnsafeRead v i
basicUnsafeWrite (MLatV v) i (Latitude x) = GVM.basicUnsafeWrite v i x
basicClear (MLatV v) = GVM.basicClear v
basicSet (MLatV v) (Latitude x) = GVM.basicSet v x
basicUnsafeNew n = MLatV `liftM` GVM.basicUnsafeNew n
basicUnsafeReplicate n (Latitude x) = MLatV `liftM` GVM.basicUnsafeReplicate n x
basicUnsafeCopy (MLatV v1) (MLatV v2) = GVM.basicUnsafeCopy v1 v2
basicUnsafeGrow (MLatV v) n = MLatV `liftM` GVM.basicUnsafeGrow v n
#if MIN_VERSION_vector(0,11,0)
basicInitialize (MLatV v) = GVM.basicInitialize v
#endif
instance GV.Vector Vector Latitude where
basicUnsafeFreeze (MLatV v) = LatV `liftM` GV.basicUnsafeFreeze v
basicUnsafeThaw (LatV v) = MLatV `liftM` GV.basicUnsafeThaw v
basicLength (LatV v) = GV.basicLength v
basicUnsafeSlice i n (LatV v) = LatV $ GV.basicUnsafeSlice i n v
basicUnsafeIndexM (LatV v) i = Latitude `liftM` GV.basicUnsafeIndexM v i
basicUnsafeCopy (MLatV mv) (LatV v) = GV.basicUnsafeCopy mv v
elemseq _ (Latitude x) = GV.elemseq (undefined :: Vector a) x
instance GVM.MVector MVector Longitude where
basicLength (MLongV v) = GVM.basicLength v
basicUnsafeSlice i n (MLongV v) = MLongV $ GVM.basicUnsafeSlice i n v
basicOverlaps (MLongV v1) (MLongV v2) = GVM.basicOverlaps v1 v2
basicUnsafeRead (MLongV v) i = Longitude `liftM` GVM.basicUnsafeRead v i
basicUnsafeWrite (MLongV v) i (Longitude x) = GVM.basicUnsafeWrite v i x
basicClear (MLongV v) = GVM.basicClear v
basicSet (MLongV v) (Longitude x) = GVM.basicSet v x
basicUnsafeNew n = MLongV `liftM` GVM.basicUnsafeNew n
basicUnsafeReplicate n (Longitude x) = MLongV `liftM` GVM.basicUnsafeReplicate n x
basicUnsafeCopy (MLongV v1) (MLongV v2) = GVM.basicUnsafeCopy v1 v2
basicUnsafeGrow (MLongV v) n = MLongV `liftM` GVM.basicUnsafeGrow v n
#if MIN_VERSION_vector(0,11,0)
basicInitialize (MLongV v) = GVM.basicInitialize v
#endif
instance GV.Vector Vector Longitude where
basicUnsafeFreeze (MLongV v) = LongV `liftM` GV.basicUnsafeFreeze v
basicUnsafeThaw (LongV v) = MLongV `liftM` GV.basicUnsafeThaw v
basicLength (LongV v) = GV.basicLength v
basicUnsafeSlice i n (LongV v) = LongV $ GV.basicUnsafeSlice i n v
basicUnsafeIndexM (LongV v) i = Longitude `liftM` GV.basicUnsafeIndexM v i
basicUnsafeCopy (MLongV mv) (LongV v) = GV.basicUnsafeCopy mv v
elemseq _ (Longitude x) = GV.elemseq (undefined :: Vector a) x