Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Matrix n m r = Matrix (Vector n (Vector m r))
- multM :: (Arity r, Arity c, Arity c', Num a) => Matrix r c a -> Matrix c c' a -> Matrix r c' a
- mult :: (Arity m, Arity n, Num r) => Matrix n m r -> Vector m r -> Vector n r
- class Invertible n r where
- newtype Transformation d r = Transformation {
- _transformationMatrix :: Matrix (d + 1) (d + 1) r
- transformationMatrix :: Lens' (Transformation d r) (Matrix (d + 1) (d + 1) r)
- (|.|) :: (Num r, Arity (d + 1)) => Transformation d r -> Transformation d r -> Transformation d r
- inverseOf :: (Fractional r, Invertible (d + 1) r) => Transformation d r -> Transformation d r
- class IsTransformable g where
- transformBy :: Transformation (Dimension g) (NumType g) -> g -> g
- transformAllBy :: (Functor c, IsTransformable g) => Transformation (Dimension g) (NumType g) -> c g -> c g
- transformPointFunctor :: (PointFunctor g, Fractional r, d ~ Dimension (g r), Arity d, Arity (d + 1)) => Transformation d r -> g r -> g r
- translation :: (Num r, Arity d, Arity (d + 1)) => Vector d r -> Transformation d r
- scaling :: (Num r, Arity d, Arity (d + 1)) => Vector d r -> Transformation d r
- uniformScaling :: (Num r, Arity d, Arity (d + 1)) => r -> Transformation d r
- translateBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => Vector (Dimension g) (NumType g) -> g -> g
- scaleBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => Vector (Dimension g) (NumType g) -> g -> g
- scaleUniformlyBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => NumType g -> g -> g
- mkRow :: forall d r. (Arity d, Num r) => Int -> r -> Vector d r
- transRow :: forall n r. (Arity n, Arity (n + 1), Num r) => Int -> r -> Vector (n + 1) r
- rotateTo :: Num r => Vector 3 (Vector 3 r) -> Transformation 3 r
Matrices
a matrix of n rows, each of m columns, storing values of type 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 # | |
Defined in Data.Geometry.Transformation | |
(Show r, Arity n, Arity m) => Show (Matrix n m r) Source # | |
IpeWriteText r => IpeWriteText (Matrix 3 3 r) Source # | |
Defined in Data.Geometry.Ipe.Writer | |
Coordinate r => IpeReadText (Matrix 3 3 r) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError (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 #
class Invertible n r where Source #
Instances
Fractional r => Invertible 2 r Source # | |
Fractional r => Invertible 3 r Source # | |
Fractional r => Invertible 4 r Source # | |
Transformations
newtype Transformation d r Source #
A type representing a Transformation for d dimensional objects
Transformation | |
|
Instances
transformationMatrix :: Lens' (Transformation d r) (Matrix (d + 1) (d + 1) r) Source #
(|.|) :: (Num r, Arity (d + 1)) => Transformation d r -> Transformation d r -> Transformation d r Source #
Compose transformations (right to left)
inverseOf :: (Fractional r, Invertible (d + 1) r) => Transformation d r -> Transformation d r Source #
Compute the inverse transformation
>>>
inverseOf $ translation (Vector2 (10.0) (5.0))
Transformation {_transformationMatrix = Matrix Vector3 [Vector3 [1.0,0.0,-10.0],Vector3 [0.0,1.0,-5.0],Vector3 [0.0,0.0,1.0]]}
Transformable geometry objects
class IsTransformable g where Source #
A class representing types that can be transformed using a transformation
transformBy :: Transformation (Dimension g) (NumType g) -> g -> g Source #
Instances
transformAllBy :: (Functor c, IsTransformable g) => Transformation (Dimension g) (NumType g) -> c g -> c g Source #
transformPointFunctor :: (PointFunctor g, Fractional r, d ~ Dimension (g r), Arity d, Arity (d + 1)) => Transformation d r -> g r -> g r Source #
Common transformations
translation :: (Num r, Arity d, Arity (d + 1)) => Vector d r -> Transformation d r Source #
uniformScaling :: (Num r, Arity d, Arity (d + 1)) => r -> Transformation d r Source #
Functions that execute transformations
translateBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => Vector (Dimension g) (NumType g) -> g -> g Source #
scaleBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => Vector (Dimension g) (NumType g) -> g -> g Source #
scaleUniformlyBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => NumType g -> g -> g 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, Arity (n + 1), Num r) => Int -> r -> Vector (n + 1) r Source #
Row in a translation matrix transRow :: forall n r. ( Arity n, Arity (n- 1), ((n - 1) + 1) ~ n , Num r) => Int -> r -> Vector n r transRow i x = set (V.element (Proxy :: Proxy (n-1))) x $ mkRow i 1