diagrams-lib-1.3.0.8: Embedded domain-specific language for declarative graphics

Copyright(c) 2011-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.BoundingBox

Contents

Description

Bounding boxes are not very compositional (e.g. it is not possible to do anything sensible with them under rotation), so they are not used in the diagrams core. However, they do have their uses; this module provides definitions and functions for working with them.

Synopsis

Bounding boxes

data BoundingBox v n Source

A bounding box is an axis-aligned region determined by two points indicating its "lower" and "upper" corners. It can also represent an empty bounding box - the points are wrapped in Maybe.

Instances

Functor v => Functor (BoundingBox v) Source 
Eq (v n) => Eq (BoundingBox v n) Source 
Read (v n) => Read (BoundingBox v n) Source 
Show (v n) => Show (BoundingBox v n) Source 
(Additive v, Ord n) => Semigroup (BoundingBox v n) Source 
(Additive v, Ord n) => Monoid (BoundingBox v n) Source 
(Metric v, Traversable v, OrderedField n) => Enveloped (BoundingBox v n) Source 
TypeableFloat n => Traced (BoundingBox V3 n) Source 
RealFloat n => Traced (BoundingBox V2 n) Source 
(Additive v, Num n, Ord n) => HasOrigin (BoundingBox v n) Source 
AsEmpty (BoundingBox v n) Source 
(Metric v, Traversable v, OrderedField n) => Alignable (BoundingBox v n) Source 
(Additive v', Foldable v', Ord n') => Each (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') Source

Only valid if the second point is not smaller than the first.

type V (BoundingBox v n) = v Source 
type N (BoundingBox v n) = n Source 

Constructing bounding boxes

emptyBox :: BoundingBox v n Source

An empty bounding box. This is the same thing as mempty, but it doesn't require the same type constraints that the Monoid instance does.

fromCorners :: (Additive v, Foldable v, Ord n) => Point v n -> Point v n -> BoundingBox v n Source

Create a bounding box from a point that is component-wise (<=) than the other. If this is not the case, then mempty is returned.

fromPoint :: Point v n -> BoundingBox v n Source

Create a degenerate bounding "box" containing only a single point.

fromPoints :: (Additive v, Ord n) => [Point v n] -> BoundingBox v n Source

Create the smallest bounding box containing all the given points.

boundingBox :: (InSpace v n a, HasBasis v, Num n, Enveloped a) => a -> BoundingBox v n Source

Create a bounding box for any enveloped object (such as a diagram or path).

Queries on bounding boxes

isEmptyBox :: BoundingBox v n -> Bool Source

Queries whether the BoundingBox is empty.

getCorners :: BoundingBox v n -> Maybe (Point v n, Point v n) Source

Gets the lower and upper corners that define the bounding box.

getAllCorners :: (Additive v, Traversable v, Num n) => BoundingBox v n -> [Point v n] Source

Computes all of the corners of the bounding box.

boxExtents :: (Additive v, Num n) => BoundingBox v n -> v n Source

Get the size of the bounding box - the vector from the (component-wise) lesser point to the greater point.

boxCenter :: (Additive v, Fractional n) => BoundingBox v n -> Maybe (Point v n) Source

Get the center point in a bounding box.

mCenterPoint :: (InSpace v n a, HasBasis v, Num n, Enveloped a) => a -> Maybe (Point v n) Source

Get the center of a the bounding box of an enveloped object, return Nothing for object with empty envelope.

centerPoint :: (InSpace v n a, HasBasis v, Num n, Enveloped a) => a -> Point v n Source

Get the center of a the bounding box of an enveloped object, return the origin for object with empty envelope.

boxTransform :: (Additive v, Fractional n) => BoundingBox v n -> BoundingBox v n -> Maybe (Transformation v n) Source

Create a transformation mapping points from one bounding box to the other. Returns Nothing if either of the boxes are empty.

boxFit :: (InSpace v n a, HasBasis v, Enveloped a, Transformable a, Monoid a, Num n) => BoundingBox v n -> a -> a Source

Transforms an enveloped thing to fit within a BoundingBox. If the bounding box is empty, then the result is also mempty.

contains :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool Source

Check whether a point is contained in a bounding box (including its edges).

contains' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool Source

Check whether a point is strictly contained in a bounding box.

inside :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source

Test whether the first bounding box is contained inside the second.

inside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source

Test whether the first bounding box is strictly contained inside the second.

outside :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source

Test whether the first bounding box lies outside the second (although they may intersect in their boundaries).

outside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source

Test whether the first bounding box lies strictly outside the second (they do not intersect at all).

Operations on bounding boxes

union :: (Additive v, Ord n) => BoundingBox v n -> BoundingBox v n -> BoundingBox v n Source

Form the smallest bounding box containing the given two bound union. This function is just an alias for mappend.

intersection :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> BoundingBox v n Source

Form the largest bounding box contained within this given two bounding boxes, or Nothing if the two bounding boxes do not overlap at all.