{- | Bounding boxes of various numbers of dimensions, plus a class for generically handling them. -} {-# LANGUAGE TypeFamilies #-} module Data.BoundingBox ( -- * Classes BoundingBox (..), HasBBox (..), -- * Types -- ** 1 dimension R.Range (), B1.BBox1 (), -- ** 2 dimensions B2.BBox2 (), -- ** 3 dimensions B3.BBox3 (), -- ** 4 dimensions B4.BBox4 () ) where import Data.Vector import qualified Data.BoundingBox.Range as R import qualified Data.BoundingBox.B1 as B1 import qualified Data.BoundingBox.B2 as B2 import qualified Data.BoundingBox.B3 as B3 import qualified Data.BoundingBox.B4 as B4 -- | Class for dealing with bounding boxes. class BoundingBox b where -- | The type of vectors that this bounding box deals with. type Point b :: * -- | Given two corner points, construct a bounding box containing them both. (You can use any two points, given in any order, provided that they are from /opposite/ corners.) bounds :: Point b -> Point b -> b -- | Given a list of points, construct a bounding box containing them all. (Throws an exception if the list is empty.) points_bounds :: [Point b] -> b -- | Return a point containing the minimum values for all coordinates. min_bound :: b -> Point b -- | Return a point containing the maximum values for all coordinates. max_bound :: b -> Point b -- | Test whether a given point lies within a given bounding box. within_bounds :: Point b -> b -> Bool -- | Take the union of two bounding boxes. The result is a new bounding box that contains every point that the original pair of boxes contained, and probably some extra space as well. union :: b -> b -> b -- | Take the intersection of two bounding boxes. If the boxes do not overlap, return 'Nothing'. Otherwise return a bounding box containing only the points common to both original bounding boxes. isect :: b -> b -> Maybe b instance BoundingBox R.Range where type Point R.Range = Scalar bounds = R.bounds points_bounds = R.points_bounds min_bound = R.min_bound max_bound = R.max_bound within_bounds = R.within_bounds union = R.union isect = R.isect instance BoundingBox B1.BBox1 where type Point B1.BBox1 = Vector1 bounds = B1.bounds points_bounds = B1.points_bounds min_bound = B1.min_bound max_bound = B1.max_bound within_bounds = B1.within_bounds union = B1.union isect = B1.isect instance BoundingBox B2.BBox2 where type Point B2.BBox2 = Vector2 bounds = B2.bounds points_bounds = B2.points_bounds min_bound = B2.min_bound max_bound = B2.max_bound within_bounds = B2.within_bounds union = B2.union isect = B2.isect instance BoundingBox B3.BBox3 where type Point B3.BBox3 = Vector3 bounds = B3.bounds points_bounds = B3.points_bounds min_bound = B3.min_bound max_bound = B3.max_bound within_bounds = B3.within_bounds union = B3.union isect = B3.isect instance BoundingBox B4.BBox4 where type Point B4.BBox4 = Vector4 bounds = B4.bounds points_bounds = B4.points_bounds min_bound = B4.min_bound max_bound = B4.max_bound within_bounds = B4.within_bounds union = B4.union isect = B4.isect -- | Class representing things that possess a bounding box. class HasBBox x where -- | The type of bounding box. (Varies depending in the required number of dimensions.) type BBox x :: * -- | Get an object's bounding box. get_bbox :: x -> BBox x