cubicbezier-0.6.0.6: Efficient manipulating of 2D cubic bezier curves.

Safe HaskellNone
LanguageHaskell98

Geom2D

Description

Basic 2 dimensional geometry functions.

Synopsis

Documentation

module Data.Cross

pattern MV_Point :: MVector s (a, a) -> MVector s (Point a) Source #

pattern V_Point :: Vector (a, a) -> Vector (Point a) Source #

class AffineTransform a b | a -> b where Source #

Methods

transform :: Transform b -> a -> a Source #

Instances
Num a => AffineTransform (Polygon a) a Source # 
Instance details

Defined in Geom2D

Methods

transform :: Transform a -> Polygon a -> Polygon a Source #

Num a => AffineTransform (Transform a) a Source # 
Instance details

Defined in Geom2D

Num a => AffineTransform (Point a) a Source # 
Instance details

Defined in Geom2D

Methods

transform :: Transform a -> Point a -> Point a Source #

Num a => AffineTransform (ClosedPath a) a Source # 
Instance details

Defined in Geom2D.CubicBezier.Basic

Num a => AffineTransform (OpenPath a) a Source # 
Instance details

Defined in Geom2D.CubicBezier.Basic

Num a => AffineTransform (PathJoin a) a Source # 
Instance details

Defined in Geom2D.CubicBezier.Basic

Num a => AffineTransform (QuadBezier a) a Source # 
Instance details

Defined in Geom2D.CubicBezier.Basic

Num a => AffineTransform (CubicBezier a) a Source # 
Instance details

Defined in Geom2D.CubicBezier.Basic

(Floating a, Eq a) => AffineTransform (Pen a) a Source # 
Instance details

Defined in Geom2D.CubicBezier.Stroke

Methods

transform :: Transform a -> Pen a -> Pen a Source #

data Polygon a Source #

Constructors

Polygon [Point a] 
Instances
Functor Polygon Source # 
Instance details

Defined in Geom2D

Methods

fmap :: (a -> b) -> Polygon a -> Polygon b #

(<$) :: a -> Polygon b -> Polygon a #

Foldable Polygon Source # 
Instance details

Defined in Geom2D

Methods

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 #

toList :: Polygon a -> [a] #

null :: Polygon a -> Bool #

length :: Polygon a -> Int #

elem :: Eq a => a -> Polygon a -> Bool #

maximum :: Ord a => Polygon a -> a #

minimum :: Ord a => Polygon a -> a #

sum :: Num a => Polygon a -> a #

product :: Num a => Polygon a -> a #

Traversable Polygon Source # 
Instance details

Defined in Geom2D

Methods

traverse :: Applicative f => (a -> f b) -> Polygon a -> f (Polygon b) #

sequenceA :: Applicative f => Polygon (f a) -> f (Polygon a) #

mapM :: Monad m => (a -> m b) -> Polygon a -> m (Polygon b) #

sequence :: Monad m => Polygon (m a) -> m (Polygon a) #

Eq a => Eq (Polygon a) Source # 
Instance details

Defined in Geom2D

Methods

(==) :: Polygon a -> Polygon a -> Bool #

(/=) :: Polygon a -> Polygon a -> Bool #

Show a => Show (Polygon a) Source # 
Instance details

Defined in Geom2D

Methods

showsPrec :: Int -> Polygon a -> ShowS #

show :: Polygon a -> String #

showList :: [Polygon a] -> ShowS #

Num a => AffineTransform (Polygon a) a Source # 
Instance details

Defined in Geom2D

Methods

transform :: Transform a -> Polygon a -> Polygon a Source #

data Line a Source #

Constructors

Line (Point a) (Point a) 
Instances
Functor Line Source # 
Instance details

Defined in Geom2D

Methods

fmap :: (a -> b) -> Line a -> Line b #

(<$) :: a -> Line b -> Line a #

Foldable Line Source # 
Instance details

Defined in Geom2D

Methods

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 #

toList :: Line a -> [a] #

null :: Line a -> Bool #

length :: Line a -> Int #

elem :: Eq a => a -> Line a -> Bool #

maximum :: Ord a => Line a -> a #

minimum :: Ord a => Line a -> a #

sum :: Num a => Line a -> a #

product :: Num a => Line a -> a #

Traversable Line Source # 
Instance details

Defined in Geom2D

Methods

traverse :: Applicative f => (a -> f b) -> Line a -> f (Line b) #

sequenceA :: Applicative f => Line (f a) -> f (Line a) #

mapM :: Monad m => (a -> m b) -> Line a -> m (Line b) #

sequence :: Monad m => Line (m a) -> m (Line a) #

Eq a => Eq (Line a) Source # 
Instance details

Defined in Geom2D

Methods

(==) :: Line a -> Line a -> Bool #

(/=) :: Line a -> Line a -> Bool #

Show a => Show (Line a) Source # 
Instance details

Defined in Geom2D

Methods

showsPrec :: Int -> Line a -> ShowS #

show :: Line a -> String #

showList :: [Line a] -> ShowS #

data Transform a Source #

A transformation (x, y) -> (ax + by + c, dx + ey + d)

Constructors

Transform 

Fields

Instances
Functor Transform Source # 
Instance details

Defined in Geom2D

Methods

fmap :: (a -> b) -> Transform a -> Transform b #

(<$) :: a -> Transform b -> Transform a #

Foldable Transform Source # 
Instance details

Defined in Geom2D

Methods

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] #

null :: Transform a -> Bool #

length :: Transform a -> Int #

elem :: Eq a => a -> Transform a -> Bool #

maximum :: Ord a => Transform a -> a #

minimum :: Ord a => Transform a -> a #

sum :: Num a => Transform a -> a #

product :: Num a => Transform a -> a #

Traversable Transform Source # 
Instance details

Defined in Geom2D

Methods

traverse :: Applicative f => (a -> f b) -> Transform a -> f (Transform b) #

sequenceA :: Applicative f => Transform (f a) -> f (Transform a) #

mapM :: Monad m => (a -> m b) -> Transform a -> m (Transform b) #

sequence :: Monad m => Transform (m a) -> m (Transform a) #

Eq a => Eq (Transform a) Source # 
Instance details

Defined in Geom2D

Methods

(==) :: Transform a -> Transform a -> Bool #

(/=) :: Transform a -> Transform a -> Bool #

Show a => Show (Transform a) Source # 
Instance details

Defined in Geom2D

Num a => AffineTransform (Transform a) a Source # 
Instance details

Defined in Geom2D

data Point a Source #

Constructors

Point 

Fields

Instances
Functor Point Source # 
Instance details

Defined in Geom2D

Methods

fmap :: (a -> b) -> Point a -> Point b #

(<$) :: a -> Point b -> Point a #

Foldable Point Source # 
Instance details

Defined in Geom2D

Methods

fold :: Monoid m => Point m -> m #

foldMap :: Monoid m => (a -> m) -> Point a -> m #

foldr :: (a -> b -> b) -> b -> Point a -> b #

foldr' :: (a -> b -> b) -> b -> Point a -> b #

foldl :: (b -> a -> b) -> b -> Point a -> b #

foldl' :: (b -> a -> b) -> b -> Point a -> b #

foldr1 :: (a -> a -> a) -> Point a -> a #

foldl1 :: (a -> a -> a) -> Point a -> a #

toList :: Point a -> [a] #

null :: Point a -> Bool #

length :: Point a -> Int #

elem :: Eq a => a -> Point a -> Bool #

maximum :: Ord a => Point a -> a #

minimum :: Ord a => Point a -> a #

sum :: Num a => Point a -> a #

product :: Num a => Point a -> a #

Traversable Point Source # 
Instance details

Defined in Geom2D

Methods

traverse :: Applicative f => (a -> f b) -> Point a -> f (Point b) #

sequenceA :: Applicative f => Point (f a) -> f (Point a) #

mapM :: Monad m => (a -> m b) -> Point a -> m (Point b) #

sequence :: Monad m => Point (m a) -> m (Point a) #

Unbox a => Vector Vector (Point a) Source # 
Instance details

Defined in Geom2D

Unbox a => MVector MVector (Point a) Source # 
Instance details

Defined in Geom2D

Eq a => Eq (Point a) Source # 
Instance details

Defined in Geom2D

Methods

(==) :: Point a -> Point a -> Bool #

(/=) :: Point a -> Point a -> Bool #

Ord a => Ord (Point a) Source # 
Instance details

Defined in Geom2D

Methods

compare :: Point a -> Point a -> Ordering #

(<) :: Point a -> Point a -> Bool #

(<=) :: Point a -> Point a -> Bool #

(>) :: Point a -> Point a -> Bool #

(>=) :: Point a -> Point a -> Bool #

max :: Point a -> Point a -> Point a #

min :: Point a -> Point a -> Point a #

Show a => Show (Point a) Source # 
Instance details

Defined in Geom2D

Methods

showsPrec :: Int -> Point a -> ShowS #

show :: Point a -> String #

showList :: [Point a] -> ShowS #

Unbox a => Unbox (Point a) Source # 
Instance details

Defined in Geom2D

Floating e => HasNormal (Point e) Source # 
Instance details

Defined in Geom2D

Methods

normalVec :: Point e -> Point e #

Num e => VectorSpace (Point e) Source # 
Instance details

Defined in Geom2D

Associated Types

type Scalar (Point e) :: Type #

Methods

(*^) :: Scalar (Point e) -> Point e -> Point e #

(AdditiveGroup e, Num e) => InnerSpace (Point e) Source # 
Instance details

Defined in Geom2D

Methods

(<.>) :: Point e -> Point e -> Scalar (Point e) #

Num e => AdditiveGroup (Point e) Source # 
Instance details

Defined in Geom2D

Methods

zeroV :: Point e #

(^+^) :: Point e -> Point e -> Point e #

negateV :: Point e -> Point e #

(^-^) :: Point e -> Point e -> Point e #

Num a => AffineTransform (Point a) a Source # 
Instance details

Defined in Geom2D

Methods

transform :: Transform a -> Point a -> Point a Source #

newtype MVector s (Point a) Source # 
Instance details

Defined in Geom2D

newtype MVector s (Point a) = MV_Point (MVector s (a, a))
newtype Vector (Point a) Source # 
Instance details

Defined in Geom2D

newtype Vector (Point a) = V_Point (Vector (a, a))
type Scalar (Point e) Source # 
Instance details

Defined in Geom2D

type Scalar (Point e) = e

($*) :: 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.

vectorMag :: Floating a => Point a -> a Source #

The lenght of the vector.

vectorMagSquare :: Floating a => Point a -> a Source #

The lenght of the vector.

vectorAngle :: RealFloat a => Point a -> a Source #

The angle of the vector, in the range (-pi, pi].

dirVector :: Floating a => a -> Point a Source #

The unitvector with the given angle.

normVector :: Floating a => Point a -> Point a Source #

The unit vector with the same direction.

(^.^) :: Num a => Point a -> Point a -> a Source #

Dot product of two vectors.

vectorCross :: Num a => Point a -> Point a -> a Source #

Cross product of two vectors.

vectorDistance :: Floating a => Point a -> Point a -> a Source #

Distance between two vectors.

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.

flipVector :: Num a => Point a -> Point a Source #

reflect the vector over the X-axis.

turnAround :: Num a => Point a -> Point a Source #

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).

rotate90L :: Floating s => Transform s Source #

Rotate vector 90 degrees left.

rotate90R :: Floating s => Transform s Source #

Rotate vector 90 degrees right.

translate :: Num a => Point a -> Transform a Source #

Create a transform that translates by the given vector.

idTrans :: Num a => Transform a Source #

The identity transformation.