module Geom2d.Point.Internal ( Point' (..) , Point (..) , magnitude ) where import Data.AEq import Data.Fixed import Geom2d.Rotation import qualified Prelude ((^)) import Prelude hiding ((^)) import Test.QuickCheck (^) :: Num a => a -> Int -> a (^) = (Prelude.^) newtype Point' a = Point' (a,a) deriving (Show, Read, Eq) class Point p where x :: p a -> a y :: p a -> a fromCoords :: a -> a -> p a magnitude :: (Point p, Floating a, Num a) => p a -> a magnitude p = sqrt (x p ^ (2::Int) + y p ^ (2::Int)) instance Point Point' where x (Point' p) = fst p y (Point' p) = snd p fromCoords a b = Point' (a, b) instance (Eq a, Num a, Fractional a, RealFloat a) => Num (Point' a) where (Point' (p1,p2)) + (Point' (q1,q2)) = Point' (p1+q1, p2+q2) (Point' (p1,p2)) - (Point' (q1,q2)) = Point' (p1-q1, p2-q2) (Point' (m,n)) * (Point' (p,q)) = Point' (m*p - n*q, m*q + n*p) abs (Point' (m,n)) = Point' (sqrt (m^2 + n^2), 0) signum p@(Point' (m,n)) | m == fromIntegral (0::Int) && n == fromIntegral (0::Int) = Point' (m,n) | otherwise = Point' (m*l,n*l) where l = 1 / x (abs p) fromInteger n = Point' (fromInteger n, 0) negate (Point' (a,b)) = Point' (negate a, negate b) instance (Arbitrary a) => Arbitrary (Point' a) where arbitrary = curry Point' <$> arbitrary <*> arbitrary instance (Num a, AEq a, RealFloat a) => AEq (Point' a) where (Point' (m,n)) ~== (Point' (p,q)) = m^2 + n^2 ~== p^2 + q^2 && atan2 n m ~== atan2 q p instance Functor Point' where fmap f (Point' (a,b)) = Point' (f a, f b) instance Rotation Point' where angle p | magnitude p == 0 = Nothing | otherwise = Just $ atan2 (y p) (x p) rotate r (Point' (a,b)) = Point' (a * cos r - b * sin r, a * sin r + b * cos r)