{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE DefaultSignatures #-}
module Data.Intersection where
import Data.Maybe (isNothing)
import Data.Vinyl.CoRec
import Data.Vinyl.Core
import Data.Vinyl.Functor
import Data.Vinyl.Lens
data NoIntersection = NoIntersection deriving (Show,Read,Eq,Ord)
type Intersection g h = CoRec Identity (IntersectionOf g h)
type family IntersectionOf g h :: [*]
coRec :: (a ∈ as) => a -> CoRec Identity as
coRec = CoRec . Identity
class IsIntersectableWith g h where
intersect :: g -> h -> Intersection g h
intersects :: g -> h -> Bool
g `intersects` h = nonEmptyIntersection (Identity g) (Identity h) $ g `intersect` h
nonEmptyIntersection :: proxy g -> proxy h -> Intersection g h -> Bool
{-# MINIMAL intersect, nonEmptyIntersection #-}
default nonEmptyIntersection :: ( NoIntersection ∈ IntersectionOf g h
, RecApplicative (IntersectionOf g h)
)
=> proxy g -> proxy h -> Intersection g h -> Bool
nonEmptyIntersection = defaultNonEmptyIntersection
type AlwaysTrueIntersection g h = RecApplicative (IntersectionOf g h)
defaultNonEmptyIntersection :: forall g h proxy.
( NoIntersection ∈ IntersectionOf g h
, RecApplicative (IntersectionOf g h)
)
=> proxy g -> proxy h -> Intersection g h -> Bool
defaultNonEmptyIntersection _ _ = isNothing . asA @NoIntersection