Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype CWMin a = CWMin {
- _cwMin :: a
- cwMin :: forall a a. Iso (CWMin a) (CWMin a) a a
- newtype CWMax a = CWMax {
- _cwMax :: a
- cwMax :: forall a a. Iso (CWMax a) (CWMax a) a a
- data Box d p r = Box {}
- minP :: forall d p r. Lens' (Box d p r) ((:+) (CWMin (Point d r)) p)
- maxP :: forall d p r. Lens' (Box d p r) ((:+) (CWMax (Point d r)) p)
- box :: (Point d r :+ p) -> (Point d r :+ p) -> Box d p r
- fromExtent :: Arity d => Vector d (Range r) -> Box d () r
- centerPoint :: (Arity d, Fractional r) => Box d p r -> Point d r
- minPoint :: Box d p r -> Point d r :+ p
- maxPoint :: Box d p r -> Point d r :+ p
- inBox :: (Arity d, Ord r) => Point d r -> Box d p r -> Bool
- extent :: Arity d => Box d p r -> Vector d (Range r)
- size :: (Arity d, Num r) => Box d p r -> Vector d r
- widthIn :: forall proxy p i d r. (Arity d, Num r, Index' (i - 1) d) => proxy i -> Box d p r -> r
- widthIn' :: (Arity d, KnownNat d, Num r) => Int -> Box d p r -> Maybe r
- type Rectangle = Box 2
- width :: Num r => Rectangle p r -> r
- height :: Num r => Rectangle p r -> r
- corners :: Num r => Rectangle p r -> (Point 2 r :+ p, Point 2 r :+ p, Point 2 r :+ p, Point 2 r :+ p)
- class IsBoxable g where
- boundingBoxList :: (IsBoxable g, Foldable1 c, Ord (NumType g), Arity (Dimension g)) => c g -> Box (Dimension g) () (NumType g)
- boundingBoxList' :: (IsBoxable g, Ord (NumType g), Arity (Dimension g)) => [g] -> Box (Dimension g) () (NumType g)
Documentation
Coordinate wize minimum
Functor CWMin Source # | |
Foldable CWMin Source # | |
Traversable CWMin Source # | |
Eq a => Eq (CWMin a) Source # | |
Ord a => Ord (CWMin a) Source # | |
Show a => Show (CWMin a) Source # | |
Generic (CWMin a) Source # | |
(Arity d, Ord r) => Semigroup (CWMin (Point d r)) Source # | |
NFData a => NFData (CWMin a) Source # | |
type Rep (CWMin a) Source # | |
Coordinate wize maximum
Functor CWMax Source # | |
Foldable CWMax Source # | |
Traversable CWMax Source # | |
Eq a => Eq (CWMax a) Source # | |
Ord a => Ord (CWMax a) Source # | |
Show a => Show (CWMax a) Source # | |
Generic (CWMax a) Source # | |
(Arity d, Ord r) => Semigroup (CWMax (Point d r)) Source # | |
NFData a => NFData (CWMax a) Source # | |
type Rep (CWMax a) Source # | |
d-dimensional boxes
PointFunctor (Box d p) Source # | |
Coordinate r => IpeReadText (Rectangle () r) Source # | |
(Arity d, Ord r) => IsIntersectableWith (Point d r) (Box d 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 # | |
Generic (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 # | |
IsBoxable (Box d p r) Source # | |
(Ord r, Arity d) => IsIntersectableWith (Box d p r) (Box d q r) Source # | |
type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) Source # | |
type IntersectionOf (Line 2 r) (Rectangle p r) Source # | |
type IntersectionOf (Point d r) (Box d p r) Source # | |
type Rep (Box d p r) Source # | |
type NumType (Box d p r) Source # | |
type Dimension (Box d p r) Source # | |
type IntersectionOf (Box d p r) (Box d q r) Source # | |
box :: (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.
fromExtent :: Arity d => Vector d (Range r) -> Box d () r Source #
Build a d dimensional Box given d ranges.
centerPoint :: (Arity d, Fractional r) => Box d p r -> Point d r Source #
Center of the box
Functions on d-dimensonal boxes
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 (Closed 1) (Closed 10),Range (Closed 2) (Closed 20),Range (Closed 3) (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
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