Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- endPoints' :: (HasEnd s, HasStart s) => s -> (StartCore s, EndCore s)
- type Set' l = Map (Point (Dimension l) (NumType l), Point (Dimension l) (NumType l)) (NonEmpty l)
- data Associated p r = Associated {
- _endPointOf :: Set' (LineSegment 2 p r)
- _interiorTo :: Set' (LineSegment 2 p r)
- associated :: Ord r => [LineSegment 2 p r] -> [LineSegment 2 p r] -> Associated p r
- endPointOf :: Associated p r -> [LineSegment 2 p r]
- interiorTo :: Associated p r -> [LineSegment 2 p r]
- type Intersections p r = Map (Point 2 r) (Associated p r)
- data IntersectionPoint p r = IntersectionPoint {
- _intersectionPoint :: !(Point 2 r)
- _associatedSegs :: !(Associated p r)
- intersectionPoint :: forall p r. Lens' (IntersectionPoint p r) (Point 2 r)
- associatedSegs :: forall p r p. Lens (IntersectionPoint p r) (IntersectionPoint p r) (Associated p r) (Associated p r)
- isEndPointIntersection :: Associated p r -> Bool
Documentation
type Set' l = Map (Point (Dimension l) (NumType l), Point (Dimension l) (NumType l)) (NonEmpty l) Source #
data Associated p r Source #
Associated | |
|
Instances
(Eq p, Eq r) => Eq (Associated p r) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.Types (==) :: Associated p r -> Associated p r -> Bool # (/=) :: Associated p r -> Associated p r -> Bool # | |
(Show r, Show p) => Show (Associated p r) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.Types showsPrec :: Int -> Associated p r -> ShowS # show :: Associated p r -> String # showList :: [Associated p r] -> ShowS # | |
Ord r => Semigroup (Associated p r) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.Types (<>) :: Associated p r -> Associated p r -> Associated p r # sconcat :: NonEmpty (Associated p r) -> Associated p r # stimes :: Integral b => b -> Associated p r -> Associated p r # | |
Ord r => Monoid (Associated p r) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.Types mempty :: Associated p r # mappend :: Associated p r -> Associated p r -> Associated p r # mconcat :: [Associated p r] -> Associated p r # |
associated :: Ord r => [LineSegment 2 p r] -> [LineSegment 2 p r] -> Associated p r Source #
endPointOf :: Associated p r -> [LineSegment 2 p r] Source #
interiorTo :: Associated p r -> [LineSegment 2 p r] Source #
type Intersections p r = Map (Point 2 r) (Associated p r) Source #
data IntersectionPoint p r Source #
IntersectionPoint | |
|
Instances
(Eq r, Eq p) => Eq (IntersectionPoint p r) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.Types (==) :: IntersectionPoint p r -> IntersectionPoint p r -> Bool # (/=) :: IntersectionPoint p r -> IntersectionPoint p r -> Bool # | |
(Show r, Show p) => Show (IntersectionPoint p r) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.Types showsPrec :: Int -> IntersectionPoint p r -> ShowS # show :: IntersectionPoint p r -> String # showList :: [IntersectionPoint p r] -> ShowS # |
intersectionPoint :: forall p r. Lens' (IntersectionPoint p r) (Point 2 r) Source #
associatedSegs :: forall p r p. Lens (IntersectionPoint p r) (IntersectionPoint p r) (Associated p r) (Associated p r) Source #
isEndPointIntersection :: Associated p r -> Bool Source #
reports true if there is at least one segment for which this intersection point is interior.
\(O(1)\)