hgeometry-0.13: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Transformation

Description

 
Synopsis

Documentation

newtype Transformation d r Source #

A type representing a Transformation for d dimensional objects

Constructors

Transformation (Matrix (d + 1) (d + 1) r) 

Instances

Instances details
Arity (d + 1) => Functor (Transformation d) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

Methods

fmap :: (a -> b) -> Transformation d a -> Transformation d b #

(<$) :: a -> Transformation d b -> Transformation d a #

Arity (d + 1) => Foldable (Transformation d) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

Methods

fold :: Monoid m => Transformation d m -> m #

foldMap :: Monoid m => (a -> m) -> Transformation d a -> m #

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

foldr :: (a -> b -> b) -> b -> Transformation d a -> b #

foldr' :: (a -> b -> b) -> b -> Transformation d a -> b #

foldl :: (b -> a -> b) -> b -> Transformation d a -> b #

foldl' :: (b -> a -> b) -> b -> Transformation d a -> b #

foldr1 :: (a -> a -> a) -> Transformation d a -> a #

foldl1 :: (a -> a -> a) -> Transformation d a -> a #

toList :: Transformation d a -> [a] #

null :: Transformation d a -> Bool #

length :: Transformation d a -> Int #

elem :: Eq a => a -> Transformation d a -> Bool #

maximum :: Ord a => Transformation d a -> a #

minimum :: Ord a => Transformation d a -> a #

sum :: Num a => Transformation d a -> a #

product :: Num a => Transformation d a -> a #

Arity (d + 1) => Traversable (Transformation d) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Transformation d a -> f (Transformation d b) #

sequenceA :: Applicative f => Transformation d (f a) -> f (Transformation d a) #

mapM :: Monad m => (a -> m b) -> Transformation d a -> m (Transformation d b) #

sequence :: Monad m => Transformation d (m a) -> m (Transformation d a) #

(Eq r, Arity (d + 1)) => Eq (Transformation d r) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

(Ord r, Arity (d + 1)) => Ord (Transformation d r) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

(Show r, Arity (d + 1)) => Show (Transformation d r) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

type NumType (Transformation d r) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

type NumType (Transformation d r) = r

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)

identity :: (Num r, Arity (d + 1)) => Transformation d r Source #

Identity transformation; i.e. the transformation which does not change anything.

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))}

class IsTransformable g where Source #

A class representing types that can be transformed using a transformation

Methods

transformBy :: Transformation (Dimension g) (NumType g) -> g -> g Source #

Instances

Instances details
IsTransformable g => IsTransformable (Boundary g) Source # 
Instance details

Defined in Data.Geometry.Boundary

Num r => IsTransformable (Ellipse r) Source # 
Instance details

Defined in Data.Geometry.Ellipse

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

Methods

transformBy :: Transformation (Dimension (Vector d r)) (NumType (Vector d r)) -> Vector d r -> Vector d r Source #

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (Point d r) Source # 
Instance details

Defined in Data.Geometry.Transformation.Internal

Methods

transformBy :: Transformation (Dimension (Point d r)) (NumType (Point d r)) -> Point d r -> Point d r Source #

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (Line d r) Source #

Lines are transformable, via line segments

Instance details

Defined in Data.Geometry.Line

Methods

transformBy :: Transformation (Dimension (Line d r)) (NumType (Line d r)) -> Line d r -> Line d r Source #

(Arity d, Arity (d + 1), Fractional r) => IsTransformable (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (HalfLine d r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

(Arity d, Arity (d + 1), Fractional r) => IsTransformable (HalfSpace d r) Source # 
Instance details

Defined in Data.Geometry.HalfSpace

Fractional r => IsTransformable (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

transformBy :: Transformation (Dimension (Box d p r)) (NumType (Box d p r)) -> Box d p r -> Box d p r Source #

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (LineSegment d p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment.Internal

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

transformBy :: Transformation (Dimension (PolyLine d p r)) (NumType (PolyLine d p r)) -> PolyLine d p r -> PolyLine d p r Source #

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (Triangle d p r) Source # 
Instance details

Defined in Data.Geometry.Triangle

Methods

transformBy :: Transformation (Dimension (Triangle d p r)) (NumType (Triangle d p r)) -> Triangle d p r -> Triangle d p r Source #

Fractional r => IsTransformable (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

transformBy :: Transformation (Dimension (Polygon t p r)) (NumType (Polygon t p r)) -> Polygon t p r -> Polygon t p r Source #

(Fractional r, Arity d, Arity (d + 1), Arity n) => IsTransformable (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

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 :+ ())

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

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

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.

skewX :: Num r => r -> Transformation 2 r Source #

Skew transformation that keeps the y-coordinates fixed and shifts the x coordinates.

rotation :: Floating r => r -> Transformation 2 r Source #

Create a matrix that corresponds to a rotation by a radians counter-clockwise around the origin.

reflection :: Floating r => r -> Transformation 2 r Source #

Create a matrix that corresponds to a reflection in a line through the origin which makes an angle of a radians with the positive x-asis, in counter-clockwise orientation.

reflectionV :: Num r => Transformation 2 r Source #

Vertical reflection

reflectionH :: Num r => Transformation 2 r Source #

Horizontal reflection

fitToBox :: forall g r q. (IsTransformable g, IsBoxable g, NumType g ~ r, Dimension g ~ 2, Ord r, Fractional r) => Rectangle q r -> g -> g Source #

Given a rectangle r and a geometry g with its boundingbox, transform the g to fit r.

fitToBoxTransform :: forall g r q. (IsTransformable g, IsBoxable g, NumType g ~ r, Dimension g ~ 2, Ord r, Fractional r) => Rectangle q r -> g -> Transformation 2 r Source #

Given a rectangle r and a geometry g with its boundingbox, compute a transformation can fit g to r.