Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Defines a data type for representing intersections. Mostly useful for the more geometric types.
Synopsis
- data NoIntersection = NoIntersection
- type Intersection g h = CoRec Identity (IntersectionOf g h)
- type family IntersectionOf g h :: [*]
- coRec :: a ∈ as => a -> CoRec Identity as
- class IsIntersectableWith g h where
- intersect :: g -> h -> Intersection g h
- intersects :: g -> h -> Bool
- nonEmptyIntersection :: proxy g -> proxy h -> Intersection g h -> Bool
- 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
Documentation
data NoIntersection Source #
A simple data type expressing that there are no intersections
Instances
Eq NoIntersection Source # | |
Defined in Data.Intersection (==) :: NoIntersection -> NoIntersection -> Bool # (/=) :: NoIntersection -> NoIntersection -> Bool # | |
Ord NoIntersection Source # | |
Defined in Data.Intersection compare :: NoIntersection -> NoIntersection -> Ordering # (<) :: NoIntersection -> NoIntersection -> Bool # (<=) :: NoIntersection -> NoIntersection -> Bool # (>) :: NoIntersection -> NoIntersection -> Bool # (>=) :: NoIntersection -> NoIntersection -> Bool # max :: NoIntersection -> NoIntersection -> NoIntersection # min :: NoIntersection -> NoIntersection -> NoIntersection # | |
Read NoIntersection Source # | |
Defined in Data.Intersection readsPrec :: Int -> ReadS NoIntersection # readList :: ReadS [NoIntersection] # | |
Show NoIntersection Source # | |
Defined in Data.Intersection showsPrec :: Int -> NoIntersection -> ShowS # show :: NoIntersection -> String # showList :: [NoIntersection] -> ShowS # |
type Intersection g h = CoRec Identity (IntersectionOf g h) Source #
The result of interesecting two geometries is a CoRec,
type family IntersectionOf g h :: [*] Source #
The type family specifying the list of possible result types of an intersection.
Instances
type IntersectionOf (Range a) (Range a) Source # | |
Defined in Data.Range |
class IsIntersectableWith g h where Source #
intersect :: g -> h -> Intersection g h Source #
intersects :: g -> h -> Bool Source #
g intersects
h = The intersection of g and h is non-empty.
The default implementation computes the intersection of g and h, and uses nonEmptyIntersection to determine if the intersection is non-empty.
nonEmptyIntersection :: proxy g -> proxy h -> Intersection g h -> Bool Source #
Helper to implement intersects
.
nonEmptyIntersection :: (NoIntersection ∈ IntersectionOf g h, RecApplicative (IntersectionOf g h)) => proxy g -> proxy h -> Intersection g h -> Bool Source #
Helper to implement intersects
.
Instances
Ord a => IsIntersectableWith (Range a) (Range a) Source # | |
Defined in Data.Range |
type AlwaysTrueIntersection g h = RecApplicative (IntersectionOf g h) Source #
When using IntersectionOf we may need some constraints that are always true anyway.
defaultNonEmptyIntersection :: forall g h proxy. (NoIntersection ∈ IntersectionOf g h, RecApplicative (IntersectionOf g h)) => proxy g -> proxy h -> Intersection g h -> Bool Source #
Returns True iff the result is *not* a NoIntersection