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

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Box.Internal

Contents

Synopsis

d-dimensional boxes

data Box d p r Source

Constructors

Box 

Fields

_minP :: Min (Point d r) :+ p
 
_maxP :: Max (Point d r) :+ p
 

Instances

PointFunctor (Box d p) Source 
Coordinate r => IpeReadText (Rectangle () r) Source 
(Num r, Ord r) => IsIntersectableWith (Rectangle p r) (Rectangle p r) Source 
(Eq r, Eq p, Arity d) => Eq (Box d p r) Source 
(Ord r, Ord p, Arity d) => Ord (Box d p r) Source 
(Show r, Show p, Arity d) => Show (Box d p r) Source 
(Arity d, Ord r, Semigroup p) => Semigroup (Box d p r) Source 
(Num r, AlwaysTruePFT d) => IsTransformable (Box d p r) Source 
type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (Point 2 r, Point 2 r) ((:) * (LineSegment 2 () r) ([] *)))) Source 
type IntersectionOf (Line 2 r) (Rectangle p r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (LineSegment 2 () r) ([] *))) Source 
type NumType (Box d p r) = r Source 
type Dimension (Box d p r) = d Source 
type IntersectionOf (Box d p r) (Box d q r) = (:) * NoIntersection ((:) * (Box d () r) ([] *)) Source 

minP :: forall d p r. Lens' (Box d p r) ((:+) (Min (Point d r)) p) Source

maxP :: forall d p r. Lens' (Box d p r) ((:+) (Max (Point d r)) p) Source

fromCornerPoints :: (Point d r :+ p) -> (Point d r :+ p) -> Box d p r Source

Given the point with the lowest coordinates and the point with highest coordinates, create a box.

Functions on d-dimensonal boxes

minPoint :: Box d p r -> Point d r :+ p Source

maxPoint :: Box d p r -> Point d r :+ p Source

inBox :: (Arity d, Ord r) => Point d r -> Box d p r -> Bool Source

Check if a point lies a box

>>> origin `inBox` (boundingBoxList' [point3 1 2 3, point3 10 20 30] :: Box 3 () Int)
False
>>> origin `inBox` (boundingBoxList' [point3 (-1) (-2) (-3), point3 10 20 30] :: Box 3 () Int)
True

extent :: Arity d => Box d p r -> Vector d (Range r) Source

Get a vector with the extent of the box in each dimension. Note that the resulting vector is 0 indexed whereas one would normally count dimensions starting at zero.

>>> extent (boundingBoxList' [point3 1 2 3, point3 10 20 30] :: Box 3 () Int)
Vector3 [Range {_lower = Closed 1, _upper = Closed 10},Range {_lower = Closed 2, _upper = Closed 20},Range {_lower = Closed 3, _upper = Closed 30}]

size :: (Arity d, Num r) => Box d p r -> Vector d r Source

Get the size of the box (in all dimensions). Note that the resulting vector is 0 indexed whereas one would normally count dimensions starting at zero.

>>> size (boundingBoxList' [origin, point3 1 2 3] :: Box 3 () Int)
Vector3 [1,2,3]

widthIn :: forall proxy p i d r. (Arity d, Num r, Index' (i - 1) d) => proxy i -> Box d p r -> r Source

Given a dimension, get the width of the box in that dimension. Dimensions are 1 indexed.

>>> widthIn (C :: C 1) (boundingBoxList' [origin, point3 1 2 3] :: Box 3 () Int)
1
>>> widthIn (C :: C 3) (boundingBoxList' [origin, point3 1 2 3] :: Box 3 () Int)
3

widthIn' :: (Arity d, KnownNat d, Num r) => Int -> Box d p r -> Maybe r Source

Same as widthIn but with a runtime int instead of a static dimension.

>>> widthIn' 1 (boundingBoxList' [origin, point3 1 2 3] :: Box 3 () Int)
Just 1
>>> widthIn' 3 (boundingBoxList' [origin, point3 1 2 3] :: Box 3 () Int)
Just 3
>>> widthIn' 10 (boundingBoxList' [origin, point3 1 2 3] :: Box 3 () Int)
Nothing

Rectangles, aka 2-dimensional boxes

width :: Num r => Rectangle p r -> r Source

height :: Num r => Rectangle p r -> r Source

corners :: Num r => Rectangle p r -> (Point 2 r :+ p, Point 2 r :+ p, Point 2 r :+ p, Point 2 r :+ p) Source

Get the corners of a rectangle, the order is: (TopLeft, TopRight, BottomRight, BottomLeft). The extra values in the Top points are taken from the Top point, the extra values in the Bottom points are taken from the Bottom point

Constructing bounding boxes

class IsBoxable g where Source

Methods

boundingBox :: (Monoid p, Semigroup p, Ord (NumType g)) => g -> Box (Dimension g) p (NumType g) Source

Instances

boundingBoxList' :: (IsBoxable g, Monoid p, Ord (NumType g), IsAlwaysTrueBoundingBox g p) => [g] -> Box (Dimension g) p (NumType g) Source

Unsafe version of boundingBoxList, that does not check if the list is non-empty