{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE InstanceSigs #-}
module Data.Geometry.Box.Internal where
import Control.DeepSeq
import Control.Lens
import Data.Bifoldable
import Data.Bifunctor
import Data.Bitraversable
import Data.Ext
import qualified Data.Foldable as F
import Data.Geometry.Point
import Data.Geometry.Properties
import Data.Geometry.Transformation
import Data.Geometry.Vector
import qualified Data.Geometry.Vector as V
import qualified Data.List.NonEmpty as NE
import qualified Data.Range as R
import qualified Data.Semigroup.Foldable as F
import qualified Data.Vector.Fixed as FV
import Data.Vinyl.CoRec (asA)
import GHC.Generics (Generic)
import GHC.TypeLits
import Test.QuickCheck (Arbitrary(..))
newtype CWMin a = CWMin { _cwMin :: a }
deriving (Show,Eq,Ord,Functor,Foldable,Traversable,Generic,NFData)
makeLenses ''CWMin
instance (Arity d, Ord r) => Semigroup (CWMin (Point d r)) where
(CWMin p) <> (CWMin q) = CWMin . Point $ FV.zipWith min (p^.vector) (q^.vector)
newtype CWMax a = CWMax { _cwMax :: a }
deriving (Show,Eq,Ord,Functor,Foldable,Traversable,Generic,NFData)
makeLenses ''CWMax
instance (Arity d, Ord r) => Semigroup (CWMax (Point d r)) where
(CWMax p) <> (CWMax q) = CWMax . Point $ FV.zipWith max (p^.vector) (q^.vector)
data Box d p r = Box { _minP :: !(CWMin (Point d r) :+ p)
, _maxP :: !(CWMax (Point d r) :+ p)
} deriving Generic
makeLenses ''Box
box :: Point d r :+ p -> Point d r :+ p -> Box d p r
box low high = Box (low&core %~ CWMin) (high&core %~ CWMax)
grow :: (Num r, Arity d) => r -> Box d p r -> Box d p r
grow x b = let v = V.replicate x
in b&minP.core.cwMin %~ (.-^ v)
&maxP.core.cwMax %~ (.+^ v)
fromExtent :: Arity d => Vector d (R.Range r) -> Box d () r
fromExtent rs = Box (CWMin (Point $ fmap (^.R.lower.R.unEndPoint) rs) :+ mempty)
(CWMax (Point $ fmap (^.R.upper.R.unEndPoint) rs) :+ mempty)
fromCenter :: (Arity d, Fractional r) => Point d r -> Vector d r -> Box d () r
fromCenter c ws = let f x r = R.ClosedRange (x-r) (x+r)
in fromExtent $ FV.zipWith f (toVec c) ((/2) <$> ws)
centerPoint :: (Arity d, Fractional r) => Box d p r -> Point d r
centerPoint b = Point $ w V.^/ 2
where w = b^.minP.core.cwMin.vector V.^+^ b^.maxP.core.cwMax.vector
deriving instance (Show r, Show p, Arity d) => Show (Box d p r)
deriving instance (Eq r, Eq p, Arity d) => Eq (Box d p r)
deriving instance (Ord r, Ord p, Arity d) => Ord (Box d p r)
instance (Arity d, Ord r, Semigroup p) => Semigroup (Box d p r) where
(Box mi ma) <> (Box mi' ma') = Box (mi <> mi') (ma <> ma')
type instance IntersectionOf (Box d p r) (Box d q r) = '[ NoIntersection, Box d () r]
instance (Ord r, Arity d) => (Box d p r) `IsIntersectableWith` (Box d q r) where
nonEmptyIntersection = defaultNonEmptyIntersection
bx `intersect` bx' = f . sequence $ FV.zipWith intersect' (extent bx) (extent bx')
where
f = maybe (coRec NoIntersection) (coRec . fromExtent)
r `intersect'` s = asA @(R.Range r) $ r `intersect` s
instance Arity d => Bifunctor (Box d) where
bimap = bimapDefault
instance Arity d => Bifoldable (Box d) where
bifoldMap = bifoldMapDefault
instance Arity d => Bitraversable (Box d) where
bitraverse f g (Box mi ma) = Box <$> bitraverse (tr g) f mi <*> bitraverse (tr g) f ma
where
tr :: (Traversable t, Applicative f) => (r -> f s) -> t (Point d r) -> f (t (Point d s))
tr g' = traverse $ traverse g'
type instance IntersectionOf (Point d r) (Box d p r) = '[ NoIntersection, Point d r]
instance (Arity d, Ord r) => (Point d r) `IsIntersectableWith` (Box d p r) where
nonEmptyIntersection = defaultNonEmptyIntersection
p `intersect` b
| not $ p `inBox` b = coRec NoIntersection
| otherwise = coRec p
instance PointFunctor (Box d p) where
pmap f (Box mi ma) = Box (first (fmap f) mi) (first (fmap f) ma)
instance (Fractional r, Arity d, Arity (d + 1))
=> IsTransformable (Box d p r) where
transformBy = transformPointFunctor
instance (Arbitrary r, Arity d, Ord r) => Arbitrary (Box d () r) where
arbitrary = (\p (q :: Point d r) -> boundingBoxList' [p,q]) <$> arbitrary <*> arbitrary
type instance Dimension (Box d p r) = d
type instance NumType (Box d p r) = r
minPoint :: Box d p r -> Point d r :+ p
minPoint b = let (CWMin p :+ e) = b^.minP in p :+ e
maxPoint :: Box d p r -> Point d r :+ p
maxPoint b = let (CWMax p :+ e) = b^.maxP in p :+ e
inBox :: (Arity d, Ord r) => Point d r -> Box d p r -> Bool
p `inBox` b = FV.and . FV.zipWith R.inRange (toVec p) . extent $ b
extent :: Arity d
=> Box d p r -> Vector d (R.Range r)
extent (Box (CWMin a :+ _) (CWMax b :+ _)) = FV.zipWith R.ClosedRange (toVec a) (toVec b)
size :: (Arity d, Num r) => Box d p r -> Vector d r
size = fmap R.width . extent
widthIn :: forall proxy p i d r. (Arity d, Arity (i - 1), Num r, ((i-1)+1) <= d)
=> proxy i -> Box d p r -> r
widthIn _ = view (V.element (C :: C (i - 1))) . size
widthIn' :: (Arity d, Num r) => Int -> Box d p r -> Maybe r
widthIn' i = preview (V.element' (i-1)) . size
type Rectangle = Box 2
width :: Num r => Rectangle p r -> r
width = widthIn (C :: C 1)
height :: Num r => Rectangle p r -> r
height = widthIn (C :: C 2)
class IsBoxable g where
boundingBox :: Ord (NumType g) => g -> Box (Dimension g) () (NumType g)
boundingBoxList :: (IsBoxable g, F.Foldable1 c, Ord (NumType g), Arity (Dimension g))
=> c g -> Box (Dimension g) () (NumType g)
boundingBoxList = F.foldMap1 boundingBox
boundingBoxList' :: (IsBoxable g, Foldable c, Ord (NumType g), Arity (Dimension g))
=> c g -> Box (Dimension g) () (NumType g)
boundingBoxList' = boundingBoxList . NE.fromList . F.toList
instance IsBoxable (Point d r) where
boundingBox p = Box (ext $ CWMin p) (ext $ CWMax p)
instance IsBoxable (Box d p r) where
boundingBox (Box m m') = Box (m&extra .~ ()) (m'&extra .~ ())
instance IsBoxable c => IsBoxable (c :+ e) where
boundingBox = boundingBox . view core