hgeometry-0.5.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Transformation

Contents

Synopsis

Matrices

newtype Matrix n m r Source

a matrix of n rows, each of m columns, storing values of type r

Constructors

Matrix (Vector n (Vector m r)) 

Instances

(Arity n, Arity m) => Functor (Matrix n m) Source 
(Eq r, Arity n, Arity m) => Eq (Matrix n m r) Source 
(Ord r, Arity n, Arity m) => Ord (Matrix n m r) Source 
(Show r, Arity n, Arity m) => Show (Matrix n m r) Source 
IpeWriteText r => IpeWriteText (Matrix 3 3 r) Source 
Coordinate r => IpeReadText (Matrix 3 3 r) Source 

multM :: (Arity r, Arity c, Arity c', Num a) => Matrix r c a -> Matrix c c' a -> Matrix r c' a Source

mult :: (Arity m, Arity n, Num r) => Matrix n m r -> Vector m r -> Vector n r Source

Transformations

newtype Transformation d r Source

A type representing a Transformation for d dimensional objects

Constructors

Transformation 

Fields

_transformationMatrix :: Matrix (1 + d) (1 + d) r
 

Instances

Arity ((+) 1 d) => Functor (Transformation d) Source 
(Eq r, Arity ((+) 1 d)) => Eq (Transformation d r) Source 
(Ord r, Arity ((+) 1 d)) => Ord (Transformation d r) Source 
(Show r, Arity ((+) 1 d)) => Show (Transformation d r) Source 
type NumType (Transformation d r) = r Source 

(|.|) :: (Num r, Arity (1 + d)) => Transformation d r -> Transformation d r -> Transformation d r Source

Compose transformations (right to left)

Transformable geometry objects

Common transformations

translation :: (Num r, Arity (1 + d), AlwaysTrueSnoc d, Arity d, Index' ((1 + d) - 1) (1 + d)) => Vector d r -> Transformation d r Source

scaling :: (Num r, Arity (1 + d), AlwaysTrueSnoc d, Arity d) => Vector d r -> Transformation d r Source

Functions that execute transformations

type AlwaysTrueTransformation d = (Arity (1 + d), AlwaysTrueSnoc d, Arity d, Index' ((1 + d) - 1) (1 + d)) Source

Helper functions to easily create matrices

mkRow :: forall d r. (Arity d, Num r) => Int -> r -> Vector d r Source

Creates a row with zeroes everywhere, except at position i, where the value is the supplied value.

transRow :: forall n r. (Arity n, Index' (n - 1) n, Num r) => Int -> r -> Vector n r Source

Row in a translation matrix