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

Safe HaskellSafe
LanguageHaskell98

Data.SG.Matrix

Description

A module with various simple matrix operations to augment the vector stuff.

The Num instances implement proper matrix multiplication as you would expect (not element-wise multiplication).

Synopsis

Documentation

type Matrix22' a = SquareMatrix Pair a Source #

A 2x2 matrix. Primarily useful via its instances, such as Functor, Num, and Matrix.

type Matrix33' a = SquareMatrix Triple a Source #

A 3x3 matrix. Primarily useful via its instances, such as Functor, Num, and Matrix.

type Matrix44' a = SquareMatrix Quad a Source #

A 4x4 matrix. Primarily useful via its instances, such as Functor, Num, and Matrix.

newtype SquareMatrix c a Source #

A square matrix. You will almost certainly want to use Matrix22' and similar instead of this directly. It does have a variety of useful instances though, especially Functor, Num and Matrix.

Its definition is based on a square matrix being, for example, a pair of pairs or a triple of triples.

Constructors

SquareMatrix (c (c a)) 

Instances

Functor c => Functor (SquareMatrix c) Source # 

Methods

fmap :: (a -> b) -> SquareMatrix c a -> SquareMatrix c b #

(<$) :: a -> SquareMatrix c b -> SquareMatrix c a #

Applicative c => Applicative (SquareMatrix c) Source # 

Methods

pure :: a -> SquareMatrix c a #

(<*>) :: SquareMatrix c (a -> b) -> SquareMatrix c a -> SquareMatrix c b #

(*>) :: SquareMatrix c a -> SquareMatrix c b -> SquareMatrix c b #

(<*) :: SquareMatrix c a -> SquareMatrix c b -> SquareMatrix c a #

Foldable c => Foldable (SquareMatrix c) Source # 

Methods

fold :: Monoid m => SquareMatrix c m -> m #

foldMap :: Monoid m => (a -> m) -> SquareMatrix c a -> m #

foldr :: (a -> b -> b) -> b -> SquareMatrix c a -> b #

foldr' :: (a -> b -> b) -> b -> SquareMatrix c a -> b #

foldl :: (b -> a -> b) -> b -> SquareMatrix c a -> b #

foldl' :: (b -> a -> b) -> b -> SquareMatrix c a -> b #

foldr1 :: (a -> a -> a) -> SquareMatrix c a -> a #

foldl1 :: (a -> a -> a) -> SquareMatrix c a -> a #

toList :: SquareMatrix c a -> [a] #

null :: SquareMatrix c a -> Bool #

length :: SquareMatrix c a -> Int #

elem :: Eq a => a -> SquareMatrix c a -> Bool #

maximum :: Ord a => SquareMatrix c a -> a #

minimum :: Ord a => SquareMatrix c a -> a #

sum :: Num a => SquareMatrix c a -> a #

product :: Num a => SquareMatrix c a -> a #

Traversable c => Traversable (SquareMatrix c) Source # 

Methods

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

sequenceA :: Applicative f => SquareMatrix c (f a) -> f (SquareMatrix c a) #

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

sequence :: Monad m => SquareMatrix c (m a) -> m (SquareMatrix c a) #

(Applicative c, Foldable c, Traversable c, Functor c) => Matrix (SquareMatrix c) Source # 
(Foldable c, Applicative c, Eq a) => Eq (SquareMatrix c a) Source # 

Methods

(==) :: SquareMatrix c a -> SquareMatrix c a -> Bool #

(/=) :: SquareMatrix c a -> SquareMatrix c a -> Bool #

(Num a, Traversable c, Foldable c, Functor c, Applicative c) => Num (SquareMatrix c a) Source # 
(Read a, Num a, Applicative c, Traversable c) => Read (SquareMatrix c a) Source # 
(Applicative c, Foldable c, Traversable c, Functor c, Show a) => Show (SquareMatrix c a) Source # 

class Matrix m where Source #

The class that all matrices belong to.

Minimal complete definition

matrixComponents, fromMatrixComponents, transpose

Methods

matrixComponents :: m a -> [[a]] Source #

Gives back the matrix as a list of rows.

fromMatrixComponents :: Num a => [[a]] -> m a Source #

Creates a matrix from a list of rows. Any missing entries are filled in with the relevant entries from the identity matrix, hence the identity matrix is equivalent to fromMatrixComponents [].

transpose :: m a -> m a Source #

Transposes a matrix

identityMatrix :: (Num a, Matrix m) => m a Source #

The identity matrix.

multMatrix :: (Foldable c, Applicative c, Num a, IsomorphicVectors c p, IsomorphicVectors p c) => SquareMatrix c a -> p a -> p a Source #

Matrix multiplication where the size of the vector matches the dimensions of the matrix. The complicated type just means that this function will work for any combination of matrix types and vectors where the width of the square matrix is the same as the number of dimensions in the vector.

multMatrixGen :: (Coord p, Matrix m, Num a) => m a -> p a -> p a Source #

Matrix multiplication. There is no requirement that the size of the matrix matches the size of the vector:

  • If the vector is too small for the matrix (e.g. multiplying a 4x4 matrix by a 3x3 vector), 1 will be used for the missing vector entries.
  • If the matrix is too small for the vector (e.g. multiplying a 2x2 matrix by a 3x3 vector), the other components of the vector will be left untouched.

This allows you to do tricks such as multiplying a 4x4 matrix by a 3D vector, and doing translation (a standard 3D graphics trick).

translate2D :: (Num a, IsomorphicVectors p Pair) => p a -> Matrix33' a Source #

Given a 2D relative vector, produces a matrix that will translate by that much (when you multiply a 2D point with it using multMatrixGen)

translate3D :: (Num a, IsomorphicVectors p Triple) => p a -> Matrix44' a Source #

Given a 3D relative vector, produces a matrix that will translate by that much (when you multiply a 3D point with it using multMatrixGen)

rotateXaxis :: (Floating a, Matrix m) => a -> m a Source #

Given an angle in radians, produces a matrix that rotates anti-clockwise by that angle around the X axis. Note that this can be used to produce a 2x2, 3x3 or 4x4 matrix, but if you produce a 2x2 matrix, odd things will happen!

rotateYaxis :: (Floating a, Matrix m) => a -> m a Source #

Given an angle in radians, produces a matrix that rotates anti-clockwise by that angle around the Y axis. Note that this can be used to produce a 2x2, 3x3 or 4x4 matrix, but if you produce a 2x2 matrix, odd things will happen!

rotateZaxis :: (Floating a, Matrix m) => a -> m a Source #

Given an angle in radians, produces a matrix that rotates anti-clockwise by that angle around the Z axis. Note that this can be used to produce a 2x2 (in which case it is a rotation around the origin), 3x3 or 4x4 matrix.