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

Safe HaskellUnsafe
LanguageHaskell2010

Data.Geometry.Transformation

Contents

Synopsis

Transformations

newtype Transformation d r Source #

A type representing a Transformation for d dimensional objects

Constructors

Transformation 

Fields

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

Defined in Data.Geometry.Transformation

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

Methods

fold :: Monoid m => Transformation d m -> 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

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

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

Defined in Data.Geometry.Transformation

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

Defined in Data.Geometry.Transformation

type NumType (Transformation d r) Source # 
Instance details

Defined in Data.Geometry.Transformation

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 #

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

Methods

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

Instances
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

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

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

(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), Arity n) => IsTransformable (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

(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 #

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 #

scaling :: (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

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.