Safe Haskell | None |
---|---|
Language | Haskell98 |
Basic 2 dimensional geometry functions.
Synopsis
- module Data.VectorSpace
- module Data.Cross
- pattern MV_Point :: MVector s (a, a) -> MVector s (Point a)
- pattern V_Point :: Vector (a, a) -> Vector (Point a)
- class AffineTransform a b | a -> b where
- data Polygon a = Polygon [Point a]
- data Line a = Line (Point a) (Point a)
- data Transform a = Transform {}
- type DPoint = Point Double
- data Point a = Point {}
- ($*) :: AffineTransform a b => Transform b -> a -> a
- inverse :: (Eq a, Fractional a) => Transform a -> Maybe (Transform a)
- lineEquation :: Floating t => Line t -> (t, t, t)
- lineDistance :: Floating a => Line a -> Point a -> a
- closestPoint :: Fractional a => Line a -> Point a -> Point a
- lineIntersect :: (Ord a, Floating a) => Line a -> Line a -> a -> Maybe (Point a)
- vectorMag :: Floating a => Point a -> a
- vectorMagSquare :: Floating a => Point a -> a
- vectorAngle :: RealFloat a => Point a -> a
- dirVector :: Floating a => a -> Point a
- normVector :: Floating a => Point a -> Point a
- (^.^) :: Num a => Point a -> Point a -> a
- vectorCross :: Num a => Point a -> Point a -> a
- vectorDistance :: Floating a => Point a -> Point a -> a
- interpolateVector :: Num a => Point a -> Point a -> a -> Point a
- rotateScaleVec :: Num a => Point a -> Transform a
- flipVector :: Num a => Point a -> Point a
- turnAround :: Num a => Point a -> Point a
- rotateVec :: Floating a => Point a -> Transform a
- rotate :: Floating s => s -> Transform s
- rotate90L :: Floating s => Transform s
- rotate90R :: Floating s => Transform s
- translate :: Num a => Point a -> Transform a
- idTrans :: Num a => Transform a
Documentation
module Data.VectorSpace
module Data.Cross
class AffineTransform a b | a -> b where Source #
Instances
Num a => AffineTransform (Polygon a) a Source # | |
Num a => AffineTransform (Transform a) a Source # | |
Num a => AffineTransform (Point a) a Source # | |
Num a => AffineTransform (ClosedPath a) a Source # | |
Defined in Geom2D.CubicBezier.Basic transform :: Transform a -> ClosedPath a -> ClosedPath a Source # | |
Num a => AffineTransform (OpenPath a) a Source # | |
Num a => AffineTransform (PathJoin a) a Source # | |
Num a => AffineTransform (QuadBezier a) a Source # | |
Defined in Geom2D.CubicBezier.Basic transform :: Transform a -> QuadBezier a -> QuadBezier a Source # | |
Num a => AffineTransform (CubicBezier a) a Source # | |
Defined in Geom2D.CubicBezier.Basic transform :: Transform a -> CubicBezier a -> CubicBezier a Source # | |
(Floating a, Eq a) => AffineTransform (Pen a) a Source # | |
Instances
Functor Polygon Source # | |
Foldable Polygon Source # | |
Defined in Geom2D fold :: Monoid m => Polygon m -> m # foldMap :: Monoid m => (a -> m) -> Polygon a -> m # foldr :: (a -> b -> b) -> b -> Polygon a -> b # foldr' :: (a -> b -> b) -> b -> Polygon a -> b # foldl :: (b -> a -> b) -> b -> Polygon a -> b # foldl' :: (b -> a -> b) -> b -> Polygon a -> b # foldr1 :: (a -> a -> a) -> Polygon a -> a # foldl1 :: (a -> a -> a) -> Polygon a -> a # elem :: Eq a => a -> Polygon a -> Bool # maximum :: Ord a => Polygon a -> a # minimum :: Ord a => Polygon a -> a # | |
Traversable Polygon Source # | |
Eq a => Eq (Polygon a) Source # | |
Show a => Show (Polygon a) Source # | |
Num a => AffineTransform (Polygon a) a Source # | |
Instances
Functor Line Source # | |
Foldable Line Source # | |
Defined in Geom2D fold :: Monoid m => Line m -> m # foldMap :: Monoid m => (a -> m) -> Line a -> m # foldr :: (a -> b -> b) -> b -> Line a -> b # foldr' :: (a -> b -> b) -> b -> Line a -> b # foldl :: (b -> a -> b) -> b -> Line a -> b # foldl' :: (b -> a -> b) -> b -> Line a -> b # foldr1 :: (a -> a -> a) -> Line a -> a # foldl1 :: (a -> a -> a) -> Line a -> a # elem :: Eq a => a -> Line a -> Bool # maximum :: Ord a => Line a -> a # | |
Traversable Line Source # | |
Eq a => Eq (Line a) Source # | |
Show a => Show (Line a) Source # | |
A transformation (x, y) -> (ax + by + c, dx + ey + d)
Instances
Functor Transform Source # | |
Foldable Transform Source # | |
Defined in Geom2D fold :: Monoid m => Transform m -> m # foldMap :: Monoid m => (a -> m) -> Transform a -> m # foldr :: (a -> b -> b) -> b -> Transform a -> b # foldr' :: (a -> b -> b) -> b -> Transform a -> b # foldl :: (b -> a -> b) -> b -> Transform a -> b # foldl' :: (b -> a -> b) -> b -> Transform a -> b # foldr1 :: (a -> a -> a) -> Transform a -> a # foldl1 :: (a -> a -> a) -> Transform a -> a # toList :: Transform a -> [a] # length :: Transform a -> Int # elem :: Eq a => a -> Transform a -> Bool # maximum :: Ord a => Transform a -> a # minimum :: Ord a => Transform a -> a # | |
Traversable Transform Source # | |
Eq a => Eq (Transform a) Source # | |
Show a => Show (Transform a) Source # | |
Num a => AffineTransform (Transform a) a Source # | |
Instances
($*) :: AffineTransform a b => Transform b -> a -> a infixr 5 Source #
Operator for applying a transformation.
inverse :: (Eq a, Fractional a) => Transform a -> Maybe (Transform a) Source #
Calculate the inverse of a transformation.
lineEquation :: Floating t => Line t -> (t, t, t) Source #
Return the parameters (a, b, c) for the normalised equation
of the line: a*x + b*y + c = 0
.
lineDistance :: Floating a => Line a -> Point a -> a Source #
Return the signed distance from a point to the line. If the distance is negative, the point lies to the right of the line
closestPoint :: Fractional a => Line a -> Point a -> Point a Source #
Return the point on the line closest to the given point.
lineIntersect :: (Ord a, Floating a) => Line a -> Line a -> a -> Maybe (Point a) Source #
Calculate the intersection of two lines. If the determinant is less than tolerance (parallel or coincident lines), return Nothing.
vectorMagSquare :: Floating a => Point a -> a Source #
The lenght of the vector.
interpolateVector :: Num a => Point a -> Point a -> a -> Point a Source #
Interpolate between two vectors.
rotateScaleVec :: Num a => Point a -> Transform a Source #
Create a transform that rotates by the angle of the given vector and multiplies with the magnitude of the vector.
rotateVec :: Floating a => Point a -> Transform a Source #
Create a transform that rotates by the angle of the given vector with the x-axis
rotate :: Floating s => s -> Transform s Source #
Create a transform that rotates by the given angle (radians).