| Portability | GHC |
|---|---|
| Stability | highly unstable |
| Maintainer | Stephen Tetley <stephen.tetley@gmail.com> |
Wumpus.Core.Geometry
Contents
Description
Objects and operations for 2D geometry.
Vector, point, 3x3 matrix, and radian representations,
plus a type family DUnit for parameterizing type classes
with some dimension.
- type family DUnit a :: *
- type family GuardEq a b :: *
- data UNil u
- data Vec2 u = V2 {}
- type DVec2 = Vec2 Double
- data Point2 u = P2 {}
- type DPoint2 = Point2 Double
- data Matrix3'3 u = M3'3 !u !u !u !u !u !u !u !u !u
- type DMatrix3'3 = Matrix3'3 Double
- data Radian
- class MatrixMult t where
- uNil :: UNil u
- vec :: Num u => u -> u -> Vec2 u
- hvec :: Num u => u -> Vec2 u
- vvec :: Num u => u -> Vec2 u
- avec :: Floating u => Radian -> u -> Vec2 u
- pvec :: Num u => Point2 u -> Point2 u -> Vec2 u
- vreverse :: Num u => Vec2 u -> Vec2 u
- direction :: (Floating u, Real u) => Vec2 u -> Radian
- vlength :: Floating u => Vec2 u -> u
- vangle :: (Floating u, Real u, InnerSpace (Vec2 u)) => Vec2 u -> Vec2 u -> Radian
- zeroPt :: Num u => Point2 u
- maxPt :: Ord u => Point2 u -> Point2 u -> Point2 u
- minPt :: Ord u => Point2 u -> Point2 u -> Point2 u
- lineDirection :: (Floating u, Real u) => Point2 u -> Point2 u -> Radian
- identityMatrix :: Num u => Matrix3'3 u
- scalingMatrix :: Num u => u -> u -> Matrix3'3 u
- translationMatrix :: Num u => u -> u -> Matrix3'3 u
- rotationMatrix :: (Floating u, Real u) => Radian -> Matrix3'3 u
- originatedRotationMatrix :: (Floating u, Real u) => Radian -> Point2 u -> Matrix3'3 u
- invert :: Fractional u => Matrix3'3 u -> Matrix3'3 u
- determinant :: Num u => Matrix3'3 u -> u
- transpose :: Matrix3'3 u -> Matrix3'3 u
- toRadian :: Real a => a -> Radian
- fromRadian :: Fractional a => Radian -> a
- d2r :: (Floating a, Real a) => a -> Radian
- r2d :: (Floating a, Real a) => Radian -> a
- circularModulo :: Radian -> Radian
- bezierArc :: Floating u => u -> Radian -> Radian -> Point2 u -> (Point2 u, Point2 u, Point2 u, Point2 u)
- bezierCircle :: (Fractional u, Floating u) => Int -> u -> Point2 u -> [Point2 u]
Type family
type family DUnit a :: *Source
Some unit of dimension usually double.
This very useful for reducing the kind of type classes to *.
Doing this then allows constraints on the Unit type on the instances rather than in the class declaration.
Data types
Phantom ().
This newtype is Haskell's () with unit of dimension u as
a phantom type.
This has no use in wumpus-core, but it has affine instances
which cannot be written for (). By supporting affine
instances it becomes useful to higher-level software
(wumpus-basic employs it for the Graphic type.)
2D Vector - both components are strict.
Instances
| Functor Vec2 | |
| Eq u => Eq (Vec2 u) | |
| Show u => Show (Vec2 u) | |
| (u ~ Scalar u, Num u, InnerSpace u) => InnerSpace (Vec2 u) | |
| Num u => VectorSpace (Vec2 u) | |
| Num u => AdditiveGroup (Vec2 u) | |
| PSUnit u => Format (Vec2 u) | |
| Num u => MatrixMult (Vec2 u) | |
| Num u => Translate (Vec2 u) | |
| Num u => Scale (Vec2 u) | |
| (Floating u, Real u) => RotateAbout (Vec2 u) | |
| (Floating u, Real u) => Rotate (Vec2 u) | |
| Num u => Transform (Vec2 u) |
2D Point - both components are strict.
Note - Point2 derives Ord so it can be used as a key in Data.Map etc.
Instances
| Functor Point2 | |
| Eq u => Eq (Point2 u) | |
| Ord u => Ord (Point2 u) | |
| Show u => Show (Point2 u) | |
| Num u => AffineSpace (Point2 u) | |
| PSUnit u => Format (Point2 u) | |
| Num u => MatrixMult (Point2 u) | |
| Num u => Translate (Point2 u) | |
| Num u => Scale (Point2 u) | |
| (Floating u, Real u) => RotateAbout (Point2 u) | |
| (Floating u, Real u) => Rotate (Point2 u) | |
| Num u => Transform (Point2 u) |
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 seems commplace in geometry texts, but PostScript
represents the current-transformation-matrix in
column-major form.
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 !u !u !u !u !u !u !u !u !u |
type DMatrix3'3 = Matrix3'3 DoubleSource
Radian is represented with a distinct type. Equality and ordering are approximate where the epsilon is 0.0001.
class MatrixMult t whereSource
Matrix multiplication - typically of points and vectors represented as homogeneous coordinates.
Instances
| Num u => MatrixMult (Vec2 u) | |
| Num u => MatrixMult (Point2 u) |
UNil operations
Vector operations
pvec :: Num u => Point2 u -> Point2 u -> Vec2 uSource
The vector between two points
pvec = flip (.-.)
direction :: (Floating u, Real u) => Vec2 u -> RadianSource
Direction of a vector - i.e. the counter-clockwise angle from the x-axis.
vangle :: (Floating u, Real u, InnerSpace (Vec2 u)) => Vec2 u -> Vec2 u -> RadianSource
Extract the angle between two vectors.
Point operations
maxPt :: Ord u => Point2 u -> Point2 u -> Point2 uSource
Component-wise max on points.
maxPt (P2 1 2) (Pt 2 1) = Pt 2 2
lineDirection :: (Floating u, Real u) => Point2 u -> Point2 u -> RadianSource
Calculate the counter-clockwise angle between two points and the x-axis.
Matrix contruction
identityMatrix :: Num u => Matrix3'3 uSource
Construct the identity matrix:
(M3'3 1 0 0
0 1 0
0 0 1 )
scalingMatrix :: Num u => u -> u -> Matrix3'3 uSource
Construct a scaling matrix:
(M3'3 sx 0 0
0 sy 0
0 0 1 )
translationMatrix :: Num u => u -> u -> Matrix3'3 uSource
Construct a translation matrix:
(M3'3 1 0 x
0 1 y
0 0 1 )
rotationMatrix :: (Floating u, Real u) => Radian -> Matrix3'3 uSource
Construct a rotation matrix:
(M3'3 cos(a) -sin(a) 0
sin(a) cos(a) 0
0 0 1 )
originatedRotationMatrix :: (Floating u, Real u) => Radian -> Point2 u -> Matrix3'3 uSource
Construct a matrix for rotation about some point.
This is the product of three matrices: T R T^-1
(T being the translation matrix, R the rotation matrix and T^-1 the inverse of the translation matrix).
matrix operations
invert :: Fractional u => Matrix3'3 u -> Matrix3'3 uSource
Invert a matrix.
determinant :: Num u => Matrix3'3 u -> uSource
Determinant of a matrix.
Radian operations
fromRadian :: Fractional a => Radian -> aSource
Convert from radians.
circularModulo :: Radian -> RadianSource
Modulo a (positive) angle into the range 0..2*pi.
Bezier curves
bezierArc :: Floating u => u -> Radian -> Radian -> Point2 u -> (Point2 u, Point2 u, Point2 u, Point2 u)Source
bezierArc : radius * ang1 * ang2 * center ->
(start_point, control_point1, control_point2, end_point)
Create an arc - this construction is the analogue of
PostScript's arc command, but the arc is created as a
Bezier curve so it should span less than 90deg.
CAVEAT - ang2 must be greater than ang1
bezierCircle :: (Fractional u, Floating u) => Int -> u -> Point2 u -> [Point2 u]Source
bezierCircle : n * radius * center -> [Point]
Make a circle from Bezier curves - n is the number of
subdivsions per quadrant.