SGplus-1.1: (updated) Small geometry library for dealing with vectors and collision detection

Safe HaskellSafe
LanguageHaskell98

Data.SG.Geometry.TwoDim

Description

A module with types to use in a 2D system, and various helper functions. Several more functions are available for use in the Data.SG.Geometry module.

Synopsis

Documentation

newtype Point2' a Source #

A point in 2D space.

Constructors

Point2 (a, a) 

Instances

Functor Point2' Source # 

Methods

fmap :: (a -> b) -> Point2' a -> Point2' b #

(<$) :: a -> Point2' b -> Point2' a #

Applicative Point2' Source # 

Methods

pure :: a -> Point2' a #

(<*>) :: Point2' (a -> b) -> Point2' a -> Point2' b #

(*>) :: Point2' a -> Point2' b -> Point2' b #

(<*) :: Point2' a -> Point2' b -> Point2' a #

Foldable Point2' Source # 

Methods

fold :: Monoid m => Point2' m -> m #

foldMap :: Monoid m => (a -> m) -> Point2' a -> m #

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

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

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

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

foldr1 :: (a -> a -> a) -> Point2' a -> a #

foldl1 :: (a -> a -> a) -> Point2' a -> a #

toList :: Point2' a -> [a] #

null :: Point2' a -> Bool #

length :: Point2' a -> Int #

elem :: Eq a => a -> Point2' a -> Bool #

maximum :: Ord a => Point2' a -> a #

minimum :: Ord a => Point2' a -> a #

sum :: Num a => Point2' a -> a #

product :: Num a => Point2' a -> a #

Traversable Point2' Source # 

Methods

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

sequenceA :: Applicative f => Point2' (f a) -> f (Point2' a) #

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

sequence :: Monad m => Point2' (m a) -> m (Point2' a) #

VectorNum Point2' Source # 

Methods

fmapNum1 :: Num b => (a -> b) -> Point2' a -> Point2' b Source #

fmapNum2 :: Num c => (a -> b -> c) -> Point2' a -> Point2' b -> Point2' c Source #

fmapNum1inv :: Num a => (a -> a) -> Point2' a -> Point2' a Source #

simpleVec :: Num a => a -> Point2' a Source #

Coord2 Point2' Source # 

Methods

getX :: Point2' a -> a Source #

getY :: Point2' a -> a Source #

Coord Point2' Source # 

Methods

getComponents :: Num a => Point2' a -> [a] Source #

fromComponents :: Num a => [a] -> Point2' a Source #

magSq :: Num a => Point2' a -> a Source #

dotProduct :: Num a => Point2' a -> Point2' a -> a Source #

IsomorphicVectors Pair Point2' Source # 

Methods

iso :: Num a => Pair a -> Point2' a Source #

IsomorphicVectors Rel2' Point2' Source # 

Methods

iso :: Num a => Rel2' a -> Point2' a Source #

IsomorphicVectors Point2' Pair Source # 

Methods

iso :: Num a => Point2' a -> Pair a Source #

IsomorphicVectors Point2' Rel2' Source # 

Methods

iso :: Num a => Point2' a -> Rel2' a Source #

Geometry Rel2' Point2' Line2' Source # 

Methods

scaleRel :: Num a => a -> Rel2' a -> Rel2' a Source #

plusDir :: (Num a, Eq a, Show a) => Point2' a -> Rel2' a -> Point2' a Source #

fromPt :: (Num a, Eq a, Show a) => Point2' a -> Point2' a -> Rel2' a Source #

getLineVecs :: Num a => Line2' a -> (Point2' a, Rel2' a) Source #

makeLine :: Num a => Point2' a -> Rel2' a -> Line2' a Source #

Eq a => Eq (Point2' a) Source # 

Methods

(==) :: Point2' a -> Point2' a -> Bool #

(/=) :: Point2' a -> Point2' a -> Bool #

Ord a => Ord (Point2' a) Source # 

Methods

compare :: Point2' a -> Point2' a -> Ordering #

(<) :: Point2' a -> Point2' a -> Bool #

(<=) :: Point2' a -> Point2' a -> Bool #

(>) :: Point2' a -> Point2' a -> Bool #

(>=) :: Point2' a -> Point2' a -> Bool #

max :: Point2' a -> Point2' a -> Point2' a #

min :: Point2' a -> Point2' a -> Point2' a #

Read a => Read (Point2' a) Source # 
Show a => Show (Point2' a) Source # 

Methods

showsPrec :: Int -> Point2' a -> ShowS #

show :: Point2' a -> String #

showList :: [Point2' a] -> ShowS #

data Rel2' a Source #

A relative vector (free vector) in 2D space. The pair are the x and y components, and the last item is the squared magnitude of the vector, which is stored with it to speed up various operations. It is suggested you use makeRel2 to create one of these, unless the square magnitude is easily apparent, e.g. Rel2 (0, 2) 4

Constructors

Rel2 (a, a) a 

Instances

Foldable Rel2' Source # 

Methods

fold :: Monoid m => Rel2' m -> m #

foldMap :: Monoid m => (a -> m) -> Rel2' a -> m #

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

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

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

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

foldr1 :: (a -> a -> a) -> Rel2' a -> a #

foldl1 :: (a -> a -> a) -> Rel2' a -> a #

toList :: Rel2' a -> [a] #

null :: Rel2' a -> Bool #

length :: Rel2' a -> Int #

elem :: Eq a => a -> Rel2' a -> Bool #

maximum :: Ord a => Rel2' a -> a #

minimum :: Ord a => Rel2' a -> a #

sum :: Num a => Rel2' a -> a #

product :: Num a => Rel2' a -> a #

VectorNum Rel2' Source # 

Methods

fmapNum1 :: Num b => (a -> b) -> Rel2' a -> Rel2' b Source #

fmapNum2 :: Num c => (a -> b -> c) -> Rel2' a -> Rel2' b -> Rel2' c Source #

fmapNum1inv :: Num a => (a -> a) -> Rel2' a -> Rel2' a Source #

simpleVec :: Num a => a -> Rel2' a Source #

Coord2 Rel2' Source # 

Methods

getX :: Rel2' a -> a Source #

getY :: Rel2' a -> a Source #

Coord Rel2' Source # 

Methods

getComponents :: Num a => Rel2' a -> [a] Source #

fromComponents :: Num a => [a] -> Rel2' a Source #

magSq :: Num a => Rel2' a -> a Source #

dotProduct :: Num a => Rel2' a -> Rel2' a -> a Source #

IsomorphicVectors Pair Rel2' Source # 

Methods

iso :: Num a => Pair a -> Rel2' a Source #

IsomorphicVectors Rel2' Pair Source # 

Methods

iso :: Num a => Rel2' a -> Pair a Source #

IsomorphicVectors Rel2' Point2' Source # 

Methods

iso :: Num a => Rel2' a -> Point2' a Source #

IsomorphicVectors Point2' Rel2' Source # 

Methods

iso :: Num a => Point2' a -> Rel2' a Source #

Geometry Rel2' Point2' Line2' Source # 

Methods

scaleRel :: Num a => a -> Rel2' a -> Rel2' a Source #

plusDir :: (Num a, Eq a, Show a) => Point2' a -> Rel2' a -> Point2' a Source #

fromPt :: (Num a, Eq a, Show a) => Point2' a -> Point2' a -> Rel2' a Source #

getLineVecs :: Num a => Line2' a -> (Point2' a, Rel2' a) Source #

makeLine :: Num a => Point2' a -> Rel2' a -> Line2' a Source #

Eq a => Eq (Rel2' a) Source # 

Methods

(==) :: Rel2' a -> Rel2' a -> Bool #

(/=) :: Rel2' a -> Rel2' a -> Bool #

(Show a, Eq a, Num a) => Num (Rel2' a) Source #

Multiplication doesn't make much sense, but the rest do!

Methods

(+) :: Rel2' a -> Rel2' a -> Rel2' a #

(-) :: Rel2' a -> Rel2' a -> Rel2' a #

(*) :: Rel2' a -> Rel2' a -> Rel2' a #

negate :: Rel2' a -> Rel2' a #

abs :: Rel2' a -> Rel2' a #

signum :: Rel2' a -> Rel2' a #

fromInteger :: Integer -> Rel2' a #

Ord a => Ord (Rel2' a) Source # 

Methods

compare :: Rel2' a -> Rel2' a -> Ordering #

(<) :: Rel2' a -> Rel2' a -> Bool #

(<=) :: Rel2' a -> Rel2' a -> Bool #

(>) :: Rel2' a -> Rel2' a -> Bool #

(>=) :: Rel2' a -> Rel2' a -> Bool #

max :: Rel2' a -> Rel2' a -> Rel2' a #

min :: Rel2' a -> Rel2' a -> Rel2' a #

Read a => Read (Rel2' a) Source # 
Show a => Show (Rel2' a) Source # 

Methods

showsPrec :: Int -> Rel2' a -> ShowS #

show :: Rel2' a -> String #

showList :: [Rel2' a] -> ShowS #

makeRel2 :: Num a => (a, a) -> Rel2' a Source #

Constructs a Rel2' vector.

data Line2' a Source #

A line in 2D space. A line is a point, and a free vector indicating direction. A line may be treated by a function as either finite (taking the magnitude of the free vector as the length) or infinite (ignoring the magnitude of the direction vector).

Constructors

Line2 

Instances

Geometry Rel2' Point2' Line2' Source # 

Methods

scaleRel :: Num a => a -> Rel2' a -> Rel2' a Source #

plusDir :: (Num a, Eq a, Show a) => Point2' a -> Rel2' a -> Point2' a Source #

fromPt :: (Num a, Eq a, Show a) => Point2' a -> Point2' a -> Rel2' a Source #

getLineVecs :: Num a => Line2' a -> (Point2' a, Rel2' a) Source #

makeLine :: Num a => Point2' a -> Rel2' a -> Line2' a Source #

Eq a => Eq (Line2' a) Source # 

Methods

(==) :: Line2' a -> Line2' a -> Bool #

(/=) :: Line2' a -> Line2' a -> Bool #

Read a => Read (Line2' a) Source # 
Show a => Show (Line2' a) Source # 

Methods

showsPrec :: Int -> Line2' a -> ShowS #

show :: Line2' a -> String #

showList :: [Line2' a] -> ShowS #

toAngle :: RealFloat a => Rel2' a -> a Source #

Gets the angle, in radians, anti-clockwise from the x-axis. If you pass the all-zero vector, the return value will be zero.

perpendicular2 :: Num a => Rel2' a -> Rel2' a Source #

Gets the vector perpendicular to the given 2D vector. If you pass it a vector that is in a clockwise direction around a polygon, the result will always face away from the polygon.

reflectAgainst2 :: (Floating a, Ord a, Eq a, Show a) => Rel2' a -> Rel2' a -> Rel2' a Source #

Reflects the first direction vector against the given surface normal. The resulting direction vector should have the same magnitude as the original first parameter. An example:

makeRel2 (-3, -4) `reflectAgainst2` makeRel2 (0,1) == makeRel2 (-3, 4)

reflectAgainstIfNeeded2 :: (Floating a, Ord a, Eq a, Show a) => Rel2' a -> Rel2' a -> Rel2' a Source #

Reflects the first direction vector against the given surface normal. The resulting direction vector should have the same magnitude as the original first parameter.

The reflection is not performed if the given vector points along the same direction as the normal, that is: if once projected onto the normal vector, the component is positive, the original first parameter is returned unmodified. Examples:

makeRel2 (-3, -4) `reflectAgainstIfNeeded2` makeRel2 (0,1) == makeRel2 (-3, 4)
makeRel2 (-3, 4) `reflectAgainstIfNeeded2` makeRel2 (0,1) == makeRel2 (-3, 4)

intersectLines2 :: (Fractional a, Eq a, Show a) => Line2' a -> Line2' a -> Maybe (a, a) Source #

Given two 2D lines, finds out their intersection. The first part of the result pair is how much to multiply the direction vector of the first line by (and add it to the start point of the first line) to reach the intersection, and the second part is the corresponding item for the second line. So given Just (a, b) = intersectLines2 la lb, it should be the case (minus some possible precision loss) that alongLine a la == alongLine b lb. If the lines are parallel, Nothing is returned.

Note that this function assumes the lines are infinite. If you want to check for the intersection of two finite lines, check if the two parts of the result pair are both in the range 0 to 1 inclusive.

findAllIntersections2 :: (Fractional a, Eq a, Show a) => ([Line2' a], [Line2' a]) -> [((Line2' a, a), (Line2' a, a))] Source #

Finds all the intersections between a line from the first list and a line from the second list, and how far along that is each line. That is, this is a bit like mapMaybe composed with intersectLines2 on all pairings of a line from the first list and a line from the second list.

intersectLineCircle :: (Ord a, Floating a) => Line2' a -> (Point2' a, a) -> Maybe (a, a) Source #

Given a line, and a circle (defined by a point and a radius), finds the points of intersection.

If the line does not intersect the circle, Nothing is returned. If they do intersect, two values are returned that are distances along the line. That is, given Just (a, b) = intersectLineCircle l c, the two points of intersection are (alongLine l a, alongLine l b).

The ordering of the two items in the pair is arbitrary, and if the line is a tangent to the circle, the values will be the same.

point2AtZ :: (Geometry rel pt ln, Coord3 rel, Coord3 pt, Fractional a, Eq a, Show a) => ln a -> a -> Maybe (Point2' a) Source #

Like pointAtZ, but returns a 2D vector instead of a 3D vector