{-# LANGUAGE FlexibleInstances #-} -- This module provides basic algebra with 2d-vectors -- Copyright (C) 2015, Sebastian Jordan -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation, either version 3 of the License, or -- (at your option) any later version. -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- You should have received a copy of the GNU General Public License -- along with this program. If not, see . -- | This module describes the internal structure of the `Point` type -- class and the `Point'` instance of said type class. module Geom2d.Point.Internal ( Point' (..) , Point (..) , magnitude ) where import Data.AEq import Geom2d.Rotation import qualified Prelude ((^)) import Prelude hiding ((^)) import Test.QuickCheck import Linear.V2 (^) :: Num a => a -> Int -> a (^) = (Prelude.^) -- | This data type modells the the characteristics of vectors in 2 -- dimensional space. You should construct it via `fromCoords`. 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 instance Point V2 where x (V2 r _) = r y (V2 _ r) = r fromCoords = V2 -- | Return the magnitude of a vector. 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) -- | Implementing the `Num` type class allows us to add and subtract -- vectors. Multiplication is implemented in terms of complex number -- multiplication. If you want to multiply using the dot or cross -- products use the appropriate functions from this package. instance (Eq a, Num a, Fractional a, Floating a, Point p) => Num (p a) where p + q = fromCoords (x p + x q) (y p + y q) p - q = fromCoords (x p - x q) (y p - y q) a * b = fromCoords (x a*x b - y a*y b) (x a*y b + y a*x b) abs p = fromCoords (sqrt (x p^2 + y p^2)) 0 signum p | x p == fromIntegral (0::Int) && y p == fromIntegral (0::Int) = fromCoords 0 0 | otherwise = fromCoords (x p*l) (y p*l) where l = 1 / x (abs p) fromInteger n = fromCoords (fromInteger n) 0 negate p = fromCoords (negate $ x p) (negate $ y p) 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)