Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Synopsis
- newtype Transformation d r = Transformation {
- _transformationMatrix :: Matrix (d + 1) (d + 1) r
- transformationMatrix :: Iso (Transformation d r) (Transformation d s) (Matrix (d + 1) (d + 1) r) (Matrix (d + 1) (d + 1) s)
- (|.|) :: (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
- 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
- skewX :: Num r => r -> Transformation 2 r
Documentation
>>>
import Data.Geometry.LineSegment
>>>
import Data.Ext
Transformations
newtype Transformation d r Source #
A type representing a Transformation for d dimensional objects
Transformation | |
|
Instances
transformationMatrix :: Iso (Transformation d r) (Transformation d s) (Matrix (d + 1) (d + 1) r) (Matrix (d + 1) (d + 1) s) Source #
Transformations and Matrices are isomorphic.
(|.|) :: (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 #
Apply a transformation to a collection of objects.
>>>
transformAllBy (uniformScaling 2) [Point1 1, Point1 2, Point1 3]
[Point1 2.0,Point1 4.0,Point1 6.0]
transformPointFunctor :: (PointFunctor g, Fractional r, d ~ Dimension (g r), Arity d, Arity (d + 1)) => Transformation d r -> g r -> g r Source #
Apply transformation to a PointFunctor, ie something that contains points. Polygons, triangles, line segments, etc, are all PointFunctors.
>>>
transformPointFunctor (uniformScaling 2) $ OpenLineSegment (Point1 1 :+ ()) (Point1 2 :+ ())
OpenLineSegment (Point1 2.0 :+ ()) (Point1 4.0 :+ ())
Common transformations
translation :: (Num r, Arity d, Arity (d + 1)) => Vector d r -> Transformation d r Source #
Create translation transformation from a vector.
>>>
transformBy (translation $ Vector2 1 2) $ Point2 2 3
Point2 3.0 5.0
scaling :: (Num r, Arity d, Arity (d + 1)) => Vector d r -> Transformation d r Source #
Create scaling transformation from a vector.
>>>
transformBy (scaling $ Vector2 2 (-1)) $ Point2 2 3
Point2 4.0 (-3.0)
uniformScaling :: (Num r, Arity d, Arity (d + 1)) => r -> Transformation d r Source #
Create scaling transformation from a scalar that is applied to all dimensions.
>>>
transformBy (uniformScaling 5) $ Point2 2 3
Point2 10.0 15.0>>>
uniformScaling 5 == scaling (Vector2 5 5)
True>>>
uniformScaling 5 == scaling (Vector3 5 5 5)
True
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 #
Translate a given point.
>>>
translateBy (Vector2 1 2) $ Point2 2 3
Point2 3.0 5.0
scaleBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => Vector (Dimension g) (NumType g) -> g -> g Source #
Scale a given point.
>>>
scaleBy (Vector2 2 (-1)) $ Point2 2 3
Point2 4.0 (-3.0)
scaleUniformlyBy :: (IsTransformable g, Num (NumType g), Arity (Dimension g), Arity (Dimension g + 1)) => NumType g -> g -> g Source #
Scale a given point uniformly in all dimensions.
>>>
scaleUniformlyBy 5 $ Point2 2 3
Point2 10.0 15.0
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
3D Rotations
rotateTo :: Num r => Vector 3 (Vector 3 r) -> Transformation 3 r Source #
Given three new unit-length basis vectors (u,v,w) that map to (x,y,z), construct the appropriate rotation that does this.
2D Transformations
skewX :: Num r => r -> Transformation 2 r Source #
Skew transformation that keeps the y-coordinates fixed and shifts the x coordinates.