| Portability | GHC only |
|---|---|
| Stability | experimental |
| Maintainer | stephen.tetley@gmail.com |
Wumpus.Core.Geometry
Contents
Description
2D geometry
- type family DUnit a :: *
- data Vec2 a = V2 !a !a
- type DVec2 = Vec2 Double
- data Point2 a = P2 !a !a
- type DPoint2 = Point2 Double
- data Frame2 a = Frame2 (Vec2 a) (Vec2 a) (Point2 a)
- type DFrame2 = Frame2 Double
- data Matrix3'3 a = M3'3 !a !a !a !a !a !a !a !a !a
- type DMatrix3'3 = Matrix3'3 Double
- data Radian
- class Pointwise sh where
- class MatrixMult mat t where
- type MatrixParam t :: *
- (*#) :: MatrixParam t ~ a => mat a -> t -> t
- hvec :: Num a => a -> Vec2 a
- vvec :: Num a => a -> Vec2 a
- avec :: Floating a => Radian -> a -> Vec2 a
- zeroPt :: Num a => Point2 a
- langle :: (Floating u, Real u) => Point2 u -> Point2 u -> Radian
- ortho :: Num a => Point2 a -> Frame2 a
- displaceOrigin :: Num a => Vec2 a -> Frame2 a -> Frame2 a
- pointInFrame :: Num a => Point2 a -> Frame2 a -> Point2 a
- frame2Matrix :: Num a => Frame2 a -> Matrix3'3 a
- matrix2Frame :: Matrix3'3 a -> Frame2 a
- frameProduct :: (Num a, InnerSpace (Vec2 a)) => Frame2 a -> Frame2 a -> Frame2 a
- standardFrame :: Num a => Frame2 a -> Bool
- identityMatrix :: Num a => Matrix3'3 a
- scalingMatrix :: Num a => a -> a -> Matrix3'3 a
- translationMatrix :: Num a => a -> a -> Matrix3'3 a
- rotationMatrix :: (Floating a, Real a) => Radian -> Matrix3'3 a
- originatedRotationMatrix :: (Floating a, Real a) => Radian -> Point2 a -> Matrix3'3 a
- invert :: Fractional a => Matrix3'3 a -> Matrix3'3 a
- determinant :: Num a => Matrix3'3 a -> a
- transpose :: Matrix3'3 a -> Matrix3'3 a
- req :: Radian -> Radian -> Bool
- toRadian :: Real a => a -> Radian
- fromRadian :: Fractional a => Radian -> a
- d2r :: (Floating a, Real a) => a -> Radian
- r2d :: (Floating a, Real a) => Radian -> a
Type family
Data types
Constructors
| V2 !a !a |
Instances
| Functor Vec2 | |
| Num a => MatrixMult Matrix3'3 (Vec2 a) | |
| Eq a => Eq (Vec2 a) | |
| Show a => Show (Vec2 a) | |
| Num a => Monoid (Vec2 a) | |
| Num a => VectorSpace (Vec2 a) | |
| (Scalar a ~ a, Num a, InnerSpace a) => InnerSpace (Vec2 a) | |
| Num a => AdditiveGroup (Vec2 a) | |
| Pretty a => Pretty (Vec2 a) | |
| Pointwise (Vec2 a) | |
| Num u => Translate (Vec2 u) | |
| Num u => Scale (Vec2 u) | |
| (Floating a, Real a) => RotateAbout (Vec2 a) | |
| (Floating a, Real a) => Rotate (Vec2 a) |
Constructors
| P2 !a !a |
Instances
| Functor Point2 | |
| Num a => MatrixMult Matrix3'3 (Point2 a) | |
| Eq a => Eq (Point2 a) | |
| Show a => Show (Point2 a) | |
| Num a => AffineSpace (Point2 a) | |
| Pretty a => Pretty (Point2 a) | |
| Ord a => CMinMax (Point2 a) | |
| Pointwise (Point2 a) | |
| Num u => Translate (Point2 u) | translate |
| Num u => Scale (Point2 u) | |
| (Floating a, Real a) => RotateAbout (Point2 a) | |
| (Floating a, Real a) => Rotate (Point2 a) |
A two dimensional frame.
The components are the two basis vectors e0 and e1 and
the origin o.
Typically these names for the elements will be used:
Frame2 (V2 e0x e0y) (V2 e1x e1y) (P2 ox oy)
3x3 matrix, considered to be in row-major form.
(M3'3 a b c
d e f
g h i)
For instance the rotation matrix is represented as
( cos(a) -sin(a) 0
sin(a) cos(a) 0
0 0 1 )
This is congruent with the form presented in Santos - Example 45, page 17 extended to 3x3.
ref. David A. Santos Multivariable and Vector Calculus, July 17, 2008 Version.
The right-most column is considered to represent a coordinate:
( 1 0 x
0 1 y
0 0 1 )
So a translation matrix representing the displacement in x of 40 and in y of 10 would be:
( 1 0 40
0 1 10
0 0 1 )
Constructors
| M3'3 !a !a !a !a !a !a !a !a !a |
Instances
| Functor Matrix3'3 | |
| Num a => MatrixMult Matrix3'3 (Point2 a) | |
| Num a => MatrixMult Matrix3'3 (Vec2 a) | |
| Eq a => Eq (Matrix3'3 a) | |
| Num a => Num (Matrix3'3 a) | |
| Show a => Show (Matrix3'3 a) | |
| Num a => VectorSpace (Matrix3'3 a) | |
| Num a => AdditiveGroup (Matrix3'3 a) | |
| PSUnit a => Pretty (Matrix3'3 a) | |
| ToCTM (Matrix3'3 a) |
type DMatrix3'3 = Matrix3'3 DoubleSource
Radian is represented with a distinct type. Equality and ordering are approximate where the epsilon is 0.0001.
Pointwise type class
class Pointwise sh whereSource
Pointwise is a Functor like type class, except that the container/element relationship is defined by a type family rather than a type parameter. This means that applied function must be type preserving.
Matrix multiply type class
class MatrixMult mat t whereSource
Associated Types
type MatrixParam t :: *Source
Methods
(*#) :: MatrixParam t ~ a => mat a -> t -> tSource
Instances
| Num a => MatrixMult Matrix3'3 (Point2 a) | |
| Num a => MatrixMult Matrix3'3 (Vec2 a) |
Vector operations
Point operations
Frame operations
frame2Matrix :: Num a => Frame2 a -> Matrix3'3 aSource
Concatenate the elements of the frame as columns forming a 3x3 matrix. Points and vectors are considered homogeneous coordinates - triples where the least element is either 0 indicating a vector or 1 indicating a point:
Frame (V2 e0x e0y) (V2 e1x e1y) (P2 ox oy)
becomes
(M3'3 e0x e1x ox
e0y e1y oy
0 0 1 )
matrix2Frame :: Matrix3'3 a -> Frame2 aSource
Interpret the matrix as columns forming a frame.
(M3'3 e0x e1x ox
e0y e1y oy
0 0 1 )
becomes
Frame (V2 e0x e0y) (V2 e1x e1y) (P2 ox oy)
frameProduct :: (Num a, InnerSpace (Vec2 a)) => Frame2 a -> Frame2 a -> Frame2 aSource
Multiplication of frames to form their product.
standardFrame :: Num a => Frame2 a -> BoolSource
Is the origin at (0,0) and are the basis vectors orthogonal with unit length?
Matrix contruction
identityMatrix :: Num a => Matrix3'3 aSource
Construct the identity matrix:
(M3'3 1 0 0
0 1 0
0 0 1 )
scalingMatrix :: Num a => a -> a -> Matrix3'3 aSource
Construct a scaling matrix:
(M3'3 sx 0 0
0 sy 0
0 0 1 )
translationMatrix :: Num a => a -> a -> Matrix3'3 aSource
matrix operations
invert :: Fractional a => Matrix3'3 a -> Matrix3'3 aSource
determinant :: Num a => Matrix3'3 a -> aSource
Radian operations
fromRadian :: Fractional a => Radian -> aSource