module Data.BoundingBox.B2 where
import Data.Vector.Class
import Data.Vector.V2
import qualified Data.BoundingBox.Range as R
data BBox2 = BBox2 {minX, minY, maxX, maxY :: !Scalar} deriving (Eq, Show)
rangeX :: BBox2 -> R.Range
rangeX b = R.Range (minX b) (maxX b)
rangeY :: BBox2 -> R.Range
rangeY b = R.Range (minY b) (maxY b)
rangeXY :: R.Range -> R.Range -> BBox2
rangeXY (R.Range x0 x1) (R.Range y0 y1) = BBox2 x0 y0 x1 y1
bound_corners :: Vector2 -> Vector2 -> BBox2
bound_corners (Vector2 xa ya) (Vector2 xb yb) = BBox2 (min xa xb) (min ya yb) (max xa xb) (max ya yb)
bound_points :: [Vector2] -> BBox2
bound_points ps =
let
xs = map v2x ps
ys = map v2y ps
in BBox2 (minimum xs) (minimum ys) (maximum xs) (maximum ys)
within_bounds :: Vector2 -> BBox2 -> Bool
within_bounds (Vector2 x y) b =
x `R.within_bounds` (rangeX b) &&
y `R.within_bounds` (rangeY b)
min_point :: BBox2 -> Vector2
min_point (BBox2 x0 y0 x1 y1) = Vector2 x0 y0
max_point :: BBox2 -> Vector2
max_point (BBox2 x0 y0 x1 y1) = Vector2 x1 y1
union :: BBox2 -> BBox2 -> BBox2
union b0 b1 =
let
rx = (rangeX b0) `R.union` (rangeX b1)
ry = (rangeY b0) `R.union` (rangeY b1)
in rangeXY rx ry
isect :: BBox2 -> BBox2 -> Maybe BBox2
isect b0 b1 = do
rx <- (rangeX b0) `R.isect` (rangeX b1)
ry <- (rangeY b0) `R.isect` (rangeY b1)
return (rangeXY rx ry)
unions :: [BBox2] -> BBox2
unions bs =
let
minP = map min_point bs
maxP = map max_point bs
in
BBox2
(minimum $ map v2x minP) (minimum $ map v2y minP)
(maximum $ map v2x maxP) (maximum $ map v2y maxP)