-- This module provides basic algebra with 2d-vectors and geomtric shapes -- 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 . module Geom2d.Point ( Point (..) , Point' , Triangle , Scale (..) , normalize , scaleTo , magnitude , dot , cross , triArea , pointInTriangle ) where import Linear.V2 import Geom2d.Point.Internal -- | A triangle is simply a tuple of three points. type Triangle p = (p,p,p) infixl 7 `dot`,`cross` -- | This function defines the dot product of two vectors. dot :: (Num a, Point p) => p a -> p a -> a dot a b = x a * x b + y a * y b -- | This function defined the cross product of two vectors. cross :: (Num a, Point p) => p a -> p a -> a cross a b = x a * y b - y a * x b -- | Calculate the area of a triangle. triArea :: (Point p, Num (p a), Fractional a) => Triangle (p a) -> a triArea (a,b,c) = abs $ ((b - a) `cross` (c - a)) / 2 -- | Determin whether a point is in a triangle. A point being on the -- edge is considered inside the triangle. pointInTriangle :: (Eq (p a), Num (p a), Fractional a, Point p, Ord a) => Triangle (p a) -> p a -> Bool pointInTriangle (a,b,c) p -- barycentric coordinates | b == a || c == a || b == c = False | p == a = True | otherwise = u >= 0 && v >= 0 && u + v <= 1 where u = ( v1Square * v2v0 - v1v0 * v2v1 ) / denom v = ( v0Square * v2v1 - v0v1 * v2v0 ) / denom denom = v0Square * v1Square - v0v1 * v1v0 v1Square = v1 `dot` v1 v0Square = v0 `dot` v0 v1v0 = v1 `dot` v0 v0v1 = v0 `dot` v1 v2v0 = v2 `dot` v0 v2v1 = v2 `dot` v1 v0 = c-a v1 = b-a v2 = p-a -- | This type class modells data that can be scaled by a factor. class Scale p where scale :: (Num a) => a -> p a -> p a instance Scale Point' where scale s (Point' (a,b)) = Point' (a * s, b * s) instance Scale V2 where scale r (V2 a b) = V2 (r * a) (r * b) -- | Normalizes a scaleable point to length 1. normalize :: (Scale p, Point p, Eq a, Floating a) => p a -> Maybe (p a) normalize v | magnitude v == 0 = Nothing | otherwise = Just $ scale (1/magnitude v) v scaleTo :: (Scale p, Point p, Eq a, Floating a) => a -> p a -> Maybe (p a) scaleTo s vec = scale s <$> normalize vec