module Diagrams.BoundingBox
(
BoundingBox()
, emptyBox, fromCorners, fromPoint, fromPoints
, boundingBox
, isEmptyBox
, getCorners, getAllCorners
, boxExtents, boxTransform, boxFit
, contains, contains'
, inside, inside', outside, outside'
, union, intersection
) where
import Control.Applicative ((<$>))
import qualified Data.Foldable as F
import Data.Map (Map, fromDistinctAscList, fromList,
toAscList, toList)
import Data.Maybe (fromMaybe)
import Data.VectorSpace
import Data.Basis (Basis, HasBasis, basisValue,
decompose, recompose)
import Data.Monoid (Monoid (..))
import Data.Semigroup (Option (..), Semigroup (..))
import Data.Data (Data)
import Data.Typeable (Typeable)
import Diagrams.Core.Envelope (Enveloped (..), appEnvelope)
import Diagrams.Core.HasOrigin (HasOrigin (..))
import Diagrams.Core.Points (Point (..))
import Diagrams.Core.Transform (HasLinearMap, Transformable (..),
Transformation (..), (<->))
import Diagrams.Core.V (V)
newtype NonEmptyBoundingBox v = NonEmptyBoundingBox (Point v, Point v)
deriving (Eq, Data, Typeable)
fromNonEmpty :: NonEmptyBoundingBox v -> BoundingBox v
fromNonEmpty = BoundingBox . Option . Just
fromMaybeEmpty :: Maybe (NonEmptyBoundingBox v) -> BoundingBox v
fromMaybeEmpty = maybe emptyBox fromNonEmpty
nonEmptyCorners :: NonEmptyBoundingBox v -> (Point v, Point v)
nonEmptyCorners (NonEmptyBoundingBox x) = x
instance (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> Semigroup (NonEmptyBoundingBox v) where
(NonEmptyBoundingBox (ul, uh)) <> (NonEmptyBoundingBox (vl, vh))
= NonEmptyBoundingBox
$ mapT toPoint (combineP min ul vl, combineP max uh vh)
newtype BoundingBox v = BoundingBox (Option (NonEmptyBoundingBox v))
deriving (Eq, Data, Typeable)
deriving instance
( HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v)
) => Semigroup (BoundingBox v)
deriving instance
( HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v)
) => Monoid (BoundingBox v)
type instance V (BoundingBox v) = v
mapT :: (a -> b) -> (a, a) -> (b, b)
mapT f (x, y) = (f x, f y)
instance ( VectorSpace v, HasBasis v, Ord (Basis v)
, AdditiveGroup (Scalar v), Ord (Scalar v)
) => HasOrigin (BoundingBox v) where
moveOriginTo p b
= fromMaybeEmpty
( NonEmptyBoundingBox . mapT (moveOriginTo p) <$> getCorners b )
instance ( InnerSpace v, HasBasis v, Ord (Basis v)
, AdditiveGroup (Scalar v), Ord (Scalar v), Floating (Scalar v)
) => Enveloped (BoundingBox v) where
getEnvelope = getEnvelope . getAllCorners
instance Show v => Show (BoundingBox v) where
show
= maybe "emptyBox" (\(l, u) -> "fromCorners " ++ show l ++ " " ++ show u)
. getCorners
emptyBox :: BoundingBox v
emptyBox = BoundingBox $ Option Nothing
fromCorners
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> Point v -> Point v -> BoundingBox v
fromCorners l h
| F.and (combineP (<=) l h) = fromNonEmpty $ NonEmptyBoundingBox (l, h)
| otherwise = mempty
fromPoint
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> Point v -> BoundingBox v
fromPoint p = fromNonEmpty $ NonEmptyBoundingBox (p, p)
fromPoints
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> [Point v] -> BoundingBox v
fromPoints = mconcat . map fromPoint
boundingBox :: forall a. ( Enveloped a, HasBasis (V a), AdditiveGroup (V a)
, Ord (Basis (V a))
) => a -> BoundingBox (V a)
boundingBox a = fromMaybeEmpty $ do
env <- appEnvelope $ getEnvelope a
let h = recompose $ map (\v -> (v, env $ basisValue v)) us
l = recompose $ map (\v -> (v, negate . env . negateV $ basisValue v)) us
return $ NonEmptyBoundingBox (P l, P h)
where
us = map fst $ decompose (zeroV :: V a)
isEmptyBox :: BoundingBox v -> Bool
isEmptyBox (BoundingBox (Option Nothing)) = True
isEmptyBox _ = False
getCorners :: BoundingBox v -> Maybe (Point v, Point v)
getCorners (BoundingBox p) = nonEmptyCorners <$> getOption p
getAllCorners :: (HasBasis v, AdditiveGroup (Scalar v), Ord (Basis v))
=> BoundingBox v -> [Point v]
getAllCorners (BoundingBox (Option Nothing)) = []
getAllCorners (BoundingBox (Option (Just (NonEmptyBoundingBox (l, u)))))
= map (P . recompose)
. mapM (\(b, (l', u')) -> [(b, l'), (b, u')])
. toList
$ combineP (,) l u
boxExtents :: (AdditiveGroup v) => BoundingBox v -> v
boxExtents = maybe zeroV (\(P l, P h) -> h ^-^ l) . getCorners
boxTransform :: (AdditiveGroup v, HasLinearMap v,
Fractional (Scalar v), AdditiveGroup (Scalar v), Ord (Basis v))
=> BoundingBox v -> BoundingBox v -> Maybe (Transformation v)
boxTransform u v = do
((P ul), _) <- getCorners u
((P vl), _) <- getCorners v
let lin_map = box_scale (v, u) <-> box_scale (u, v)
box_scale = combineV' (*) . uncurry (combineV' (/)) . mapT boxExtents
combineV' f x = toVector . combineV f x
return $ Transformation lin_map lin_map (vl ^-^ box_scale (v, u) ul)
boxFit :: (Enveloped a, Transformable a, Monoid a, Ord (Basis (V a)))
=> BoundingBox (V a) -> a -> a
boxFit b x = maybe mempty (`transform` x) $ boxTransform (boundingBox x) b
contains
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> Point v -> Bool
contains b p = maybe False check $ getCorners b
where
check (l, h) = F.and (combineP (<=) l p)
&& F.and (combineP (<=) p h)
contains'
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> Point v -> Bool
contains' b p = maybe False check $ getCorners b
where
check (l, h) = F.and (combineP (<) l p)
&& F.and (combineP (<) p h)
inside
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> BoundingBox v -> Bool
inside u v = fromMaybe False $ do
(ul, uh) <- getCorners u
(vl, vh) <- getCorners v
return $ F.and (combineP (>=) ul vl)
&& F.and (combineP (<=) uh vh)
inside'
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> BoundingBox v -> Bool
inside' u v = fromMaybe False $ do
(ul, uh) <- getCorners u
(vl, vh) <- getCorners v
return $ F.and (combineP (>) ul vl)
&& F.and (combineP (<) uh vh)
outside
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> BoundingBox v -> Bool
outside u v = fromMaybe True $ do
(ul, uh) <- getCorners u
(vl, vh) <- getCorners v
return $ F.or (combineP (<=) uh vl)
|| F.or (combineP (>=) ul vh)
outside'
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> BoundingBox v -> Bool
outside' u v = fromMaybe True $ do
(ul, uh) <- getCorners u
(vl, vh) <- getCorners v
return $ F.or (combineP (<) uh vl)
|| F.or (combineP (>) ul vh)
intersection
:: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> BoundingBox v -> BoundingBox v
intersection u v = maybe mempty (uncurry fromCorners) $ do
(ul, uh) <- getCorners u
(vl, vh) <- getCorners v
return $ mapT toPoint (combineP max ul vl, combineP min uh vh)
union :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v))
=> BoundingBox v -> BoundingBox v -> BoundingBox v
union = mappend
fromVector :: (HasBasis v, Ord (Basis v)) => v -> Map (Basis v) (Scalar v)
fromVector = fromList . decompose
toVector :: HasBasis v => Map (Basis v) (Scalar v) -> v
toVector = recompose . toList
toPoint :: HasBasis v => Map (Basis v) (Scalar v) -> Point v
toPoint = P . toVector
combineV :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v))
=> (Scalar v -> Scalar v -> a) -> v -> v -> Map (Basis v) a
combineV f u v = combineDefault zeroV zeroV f (fromVector u) (fromVector v)
combineP :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v))
=> (Scalar v -> Scalar v -> a) -> Point v -> Point v -> Map (Basis v) a
combineP f (P u) (P v) = combineV f u v
combineDefault :: Ord k => a -> b -> (a -> b -> c) -> Map k a -> Map k b -> Map k c
combineDefault a b f = combine g
where
g Nothing Nothing = f a b
g Nothing (Just y) = f a y
g (Just x) Nothing = f x b
g (Just x) (Just y) = f x y
combine :: Ord k => (Maybe a -> Maybe b -> c) -> Map k a -> Map k b -> Map k c
combine f am bm = fromDistinctAscList $ merge (toAscList am) (toAscList bm)
where
merge [] [] = []
merge ((x,a):xs) [] = (x, f (Just a) Nothing) : merge xs []
merge [] ((y,b):ys) = (y, f Nothing (Just b)) : merge [] ys
merge xs0@((x,a):xs) ys0@((y,b):ys) = case compare x y of
LT -> (x, f (Just a) Nothing ) : merge xs ys0
EQ -> (x, f (Just a) (Just b)) : merge xs ys
GT -> (y, f Nothing (Just b)) : merge xs0 ys