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

Safe HaskellSafe
LanguageHaskell98

Data.SG.Geometry.ThreeDim

Description

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

Synopsis

Documentation

newtype Point3' a Source #

A point in 3D space.

Constructors

Point3 (a, a, a) 

Instances

Functor Point3' Source # 

Methods

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

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

Applicative Point3' Source # 

Methods

pure :: a -> Point3' a #

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

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

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

Foldable Point3' Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: Point3' a -> Bool #

length :: Point3' a -> Int #

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

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

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

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

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

Traversable Point3' Source # 

Methods

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

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

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

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

VectorNum Point3' Source # 

Methods

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

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

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

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

Coord3 Point3' Source # 

Methods

getZ :: Point3' a -> a Source #

Coord2 Point3' Source # 

Methods

getX :: Point3' a -> a Source #

getY :: Point3' a -> a Source #

Coord Point3' Source # 

Methods

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

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

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

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

IsomorphicVectors Triple Point3' Source # 

Methods

iso :: Num a => Triple a -> Point3' a Source #

IsomorphicVectors Rel3' Point3' Source # 

Methods

iso :: Num a => Rel3' a -> Point3' a Source #

IsomorphicVectors Point3' Triple Source # 

Methods

iso :: Num a => Point3' a -> Triple a Source #

IsomorphicVectors Point3' Rel3' Source # 

Methods

iso :: Num a => Point3' a -> Rel3' a Source #

Geometry Rel3' Point3' Line3' Source # 

Methods

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

plusDir :: (Num a, Eq a, Show a) => Point3' a -> Rel3' a -> Point3' a Source #

fromPt :: (Num a, Eq a, Show a) => Point3' a -> Point3' a -> Rel3' a Source #

getLineVecs :: Num a => Line3' a -> (Point3' a, Rel3' a) Source #

makeLine :: Num a => Point3' a -> Rel3' a -> Line3' a Source #

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

Methods

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

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

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

Methods

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

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

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

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

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

max :: Point3' a -> Point3' a -> Point3' a #

min :: Point3' a -> Point3' a -> Point3' a #

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

Methods

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

show :: Point3' a -> String #

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

data Rel3' a Source #

A relative vector (free vector) in 3D space. The triple is the x, y, z 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 makeRel3 to create one of these, unless the magnitude is easily apparent, e.g. Rel3 (0, 1, 1) 2

Constructors

Rel3 (a, a, a) a 

Instances

Foldable Rel3' Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: Rel3' a -> Bool #

length :: Rel3' a -> Int #

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

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

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

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

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

VectorNum Rel3' Source # 

Methods

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

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

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

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

Coord3 Rel3' Source # 

Methods

getZ :: Rel3' a -> a Source #

Coord2 Rel3' Source # 

Methods

getX :: Rel3' a -> a Source #

getY :: Rel3' a -> a Source #

Coord Rel3' Source # 

Methods

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

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

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

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

IsomorphicVectors Triple Rel3' Source # 

Methods

iso :: Num a => Triple a -> Rel3' a Source #

IsomorphicVectors Rel3' Triple Source # 

Methods

iso :: Num a => Rel3' a -> Triple a Source #

IsomorphicVectors Rel3' Point3' Source # 

Methods

iso :: Num a => Rel3' a -> Point3' a Source #

IsomorphicVectors Point3' Rel3' Source # 

Methods

iso :: Num a => Point3' a -> Rel3' a Source #

Geometry Rel3' Point3' Line3' Source # 

Methods

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

plusDir :: (Num a, Eq a, Show a) => Point3' a -> Rel3' a -> Point3' a Source #

fromPt :: (Num a, Eq a, Show a) => Point3' a -> Point3' a -> Rel3' a Source #

getLineVecs :: Num a => Line3' a -> (Point3' a, Rel3' a) Source #

makeLine :: Num a => Point3' a -> Rel3' a -> Line3' a Source #

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

Methods

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

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

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

Methods

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

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

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

negate :: Rel3' a -> Rel3' a #

abs :: Rel3' a -> Rel3' a #

signum :: Rel3' a -> Rel3' a #

fromInteger :: Integer -> Rel3' a #

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

Methods

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

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

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

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

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

max :: Rel3' a -> Rel3' a -> Rel3' a #

min :: Rel3' a -> Rel3' a -> Rel3' a #

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

Methods

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

show :: Rel3' a -> String #

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

makeRel3 :: Num a => (a, a, a) -> Rel3' a Source #

Constructs a Rel3' vector

data Line3' a Source #

A line in 3D 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

Line3 

Instances

Geometry Rel3' Point3' Line3' Source # 

Methods

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

plusDir :: (Num a, Eq a, Show a) => Point3' a -> Rel3' a -> Point3' a Source #

fromPt :: (Num a, Eq a, Show a) => Point3' a -> Point3' a -> Rel3' a Source #

getLineVecs :: Num a => Line3' a -> (Point3' a, Rel3' a) Source #

makeLine :: Num a => Point3' a -> Rel3' a -> Line3' a Source #

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

Methods

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

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

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

Methods

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

show :: Line3' a -> String #

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