hgeometry-0.7.0.0: Geometric Algorithms, Data structures, and Data types.

Copyright(c) Frank Staals
LicenseSee LICENCE file
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Properties

Description

 
Synopsis

Documentation

type family Dimension t :: Nat Source #

A type family for types that are associated with a dimension. The dimension is the dimension of the geometry they are embedded in.

Instances
type Dimension (Boundary g) Source # 
Instance details

Defined in Data.Geometry.Boundary

type Dimension (Image r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (Image r) = 2
type Dimension (IpeSymbol r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (IpeSymbol r) = 2
type Dimension (MiniPage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (MiniPage r) = 2
type Dimension (TextLabel r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (TextLabel r) = 2
type Dimension (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (PathSegment r) = 2
type Dimension (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (Path r) = 2
type Dimension (IpeObject r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (IpeObject r) = 2
type Dimension (Group r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (Group r) = 2
type Dimension (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector

type Dimension (Vector d r) = d
type Dimension (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point

type Dimension (Point d r) = d
type Dimension (Line d r) Source # 
Instance details

Defined in Data.Geometry.Line.Internal

type Dimension (Line d r) = d
type Dimension (Interval a r) Source # 
Instance details

Defined in Data.Geometry.Interval

type Dimension (Interval a r) = 1
type Dimension (HalfLine d r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

type Dimension (HalfLine d r) = d
type Dimension (SomePolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon

type Dimension (SomePolygon p r) = 2
type Dimension (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

type Dimension (ConvexPolygon p r) = 2
type Dimension (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

type Dimension (Box d p r) = d
type Dimension (SubLine d p r) Source # 
Instance details

Defined in Data.Geometry.SubLine

type Dimension (SubLine d p r) = d
type Dimension (LineSegment d p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment

type Dimension (LineSegment d p r) = d
type Dimension (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type Dimension (PolyLine d p r) = d
type Dimension (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

type Dimension (Ball d p r) = d
type Dimension (Triangle d p r) Source # 
Instance details

Defined in Data.Geometry.Triangle

type Dimension (Triangle d p r) = d
type Dimension (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon

type Dimension (Polygon t p r) = 2
type Dimension (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

type Dimension (PlaneGraph s v e f r) = 2
type Dimension (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Dimension (PlanarSubdivision s v e f r) = 2

type family NumType t :: * Source #

A type family for types that have an associated numeric type.

Instances
type NumType (Boundary g) Source # 
Instance details

Defined in Data.Geometry.Boundary

type NumType (Boundary g) = NumType g
type NumType (Range a) Source # 
Instance details

Defined in Data.Range

type NumType (Range a) = a
type NumType (I a) Source # 
Instance details

Defined in Data.Geometry.SegmentTree.Generic

type NumType (I a) = NumType a
type NumType (Image r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (Image r) = r
type NumType (IpeSymbol r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (IpeSymbol r) = r
type NumType (MiniPage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (MiniPage r) = r
type NumType (TextLabel r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (TextLabel r) = r
type NumType (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (PathSegment r) = r
type NumType (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (Path r) = r
type NumType (IpeObject r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (IpeObject r) = r
type NumType (Group r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (Group r) = r
type NumType (Vector d r) Source # 
Instance details

Defined in Data.Geometry.Vector

type NumType (Vector d r) = r
type NumType (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point

type NumType (Point d r) = r
type NumType (Transformation d r) Source # 
Instance details

Defined in Data.Geometry.Transformation

type NumType (Transformation d r) = r
type NumType (Line d r) Source # 
Instance details

Defined in Data.Geometry.Line.Internal

type NumType (Line d r) = r
type NumType (Interval a r) Source # 
Instance details

Defined in Data.Geometry.Interval

type NumType (Interval a r) = r
type NumType (HalfLine d r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

type NumType (HalfLine d r) = r
type NumType (SomePolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon

type NumType (SomePolygon p r) = r
type NumType (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

type NumType (ConvexPolygon p r) = r
type NumType (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

type NumType (Box d p r) = r
type NumType (SubLine d p r) Source # 
Instance details

Defined in Data.Geometry.SubLine

type NumType (SubLine d p r) = r
type NumType (LineSegment d p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment

type NumType (LineSegment d p r) = r
type NumType (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type NumType (PolyLine d p r) = r
type NumType (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

type NumType (Ball d p r) = r
type NumType (Triangle d p r) Source # 
Instance details

Defined in Data.Geometry.Triangle

type NumType (Triangle d p r) = r
type NumType (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon

type NumType (Polygon t p r) = r
type NumType (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

type NumType (PlaneGraph s v e f r) = r
type NumType (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type NumType (PlanarSubdivision s v e f r) = r

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 # 
Instance details

Defined in Data.Range

type IntersectionOf (Range a) (Range a) = NoIntersection ': (Range a ': ([] :: [*]))
type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) Source # 
Instance details

Defined in Data.Geometry.Line

type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) = NoIntersection ': (Point 2 r ': ((Point 2 r, Point 2 r) ': (LineSegment 2 () r ': ([] :: [*]))))
type IntersectionOf (Line 2 r) (Boundary (Polygon t p r)) Source # 
Instance details

Defined in Data.Geometry.Polygon

type IntersectionOf (Line 2 r) (Boundary (Polygon t p r)) = Seq (Either (Point 2 r) (LineSegment 2 () r)) ': ([] :: [*])
type IntersectionOf (Line 2 r) (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.Line.Internal

type IntersectionOf (Line 2 r) (Line 2 r) = NoIntersection ': (Point 2 r ': (Line 2 r ': ([] :: [*])))
type IntersectionOf (Line 2 r) (Rectangle p r) Source # 
Instance details

Defined in Data.Geometry.Line

type IntersectionOf (Line 2 r) (Rectangle p r) = NoIntersection ': (Point 2 r ': (LineSegment 2 () r ': ([] :: [*])))
type IntersectionOf (Line 2 r) (Circle p r) Source # 
Instance details

Defined in Data.Geometry.Ball

type IntersectionOf (Line 2 r) (Circle p r) = NoIntersection ': (Touching (Point 2 r) ': ((Point 2 r, Point 2 r) ': ([] :: [*])))
type IntersectionOf (Interval a r) (Interval a r) Source # 
Instance details

Defined in Data.Geometry.Interval

type IntersectionOf (Interval a r) (Interval a r) = NoIntersection ': (Interval a r ': ([] :: [*]))
type IntersectionOf (HalfLine 2 r) (HalfLine 2 r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

type IntersectionOf (HalfLine 2 r) (HalfLine 2 r) = NoIntersection ': (Point 2 r ': (LineSegment 2 () r ': (HalfLine 2 r ': ([] :: [*]))))
type IntersectionOf (HalfLine 2 r) (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

type IntersectionOf (HalfLine 2 r) (Line 2 r) = NoIntersection ': (Point 2 r ': (HalfLine 2 r ': ([] :: [*])))
type IntersectionOf (Point d r) (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

type IntersectionOf (Point d r) (Box d p r) = NoIntersection ': (Point d r ': ([] :: [*]))
type IntersectionOf (Line 2 r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (Line 2 r) (Slab o a r) = NoIntersection ': (Line 2 r ': (LineSegment 2 a r ': ([] :: [*])))
type IntersectionOf (HalfLine 2 r) (LineSegment 2 p r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

type IntersectionOf (HalfLine 2 r) (LineSegment 2 p r) = NoIntersection ': (Point 2 r ': (LineSegment 2 () r ': ([] :: [*])))
type IntersectionOf (LineSegment 2 p r) (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.LineSegment

type IntersectionOf (LineSegment 2 p r) (Line 2 r) = NoIntersection ': (Point 2 r ': (LineSegment 2 p r ': ([] :: [*])))
type IntersectionOf (LineSegment 2 p r) (Circle q r) Source # 
Instance details

Defined in Data.Geometry.Ball

type IntersectionOf (LineSegment 2 p r) (Circle q r) = NoIntersection ': (Touching (Point 2 r) ': (Point 2 r ': ((Point 2 r, Point 2 r) ': ([] :: [*]))))
type IntersectionOf (Box d p r) (Box d q r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

type IntersectionOf (Box d p r) (Box d q r) = NoIntersection ': (Box d () r ': ([] :: [*]))
type IntersectionOf (SubLine 2 p r) (SubLine 2 q r) Source # 
Instance details

Defined in Data.Geometry.SubLine

type IntersectionOf (SubLine 2 p r) (SubLine 2 q r) = NoIntersection ': (Point 2 r ': (SubLine 2 p r ': ([] :: [*])))
type IntersectionOf (SubLine 2 p r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (SubLine 2 p r) (Slab o a r) = NoIntersection ': (SubLine 2 () r ': ([] :: [*]))
type IntersectionOf (LineSegment 2 p r) (LineSegment 2 p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment

type IntersectionOf (LineSegment 2 p r) (LineSegment 2 p r) = NoIntersection ': (Point 2 r ': (LineSegment 2 p r ': ([] :: [*])))
type IntersectionOf (LineSegment 2 p r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (LineSegment 2 p r) (Slab o a r) = NoIntersection ': (LineSegment 2 () r ': ([] :: [*]))
type IntersectionOf (Slab o a r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (Slab o a r) (Slab o a r) = NoIntersection ': (Slab o a r ': ([] :: [*]))
type IntersectionOf (Slab Horizontal a r) (Slab Vertical a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (Slab Horizontal a r) (Slab Vertical a r) = Rectangle (a, a) r ': ([] :: [*])

coRec :: a as => a -> CoRec Identity as Source #

Helper to produce a corec

class IsIntersectableWith g h where Source #

Minimal complete definition

intersect, nonEmptyIntersection

Methods

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 # 
Instance details

Defined in Data.Range

Methods

intersect :: Range a -> Range a -> Intersection (Range a) (Range a) Source #

intersects :: Range a -> Range a -> Bool Source #

nonEmptyIntersection :: proxy (Range a) -> proxy (Range a) -> Intersection (Range a) (Range a) -> Bool Source #

(Ord r, Fractional r) => IsIntersectableWith (Line 2 r) (Boundary (Rectangle p r)) Source # 
Instance details

Defined in Data.Geometry.Line

Methods

intersect :: Line 2 r -> Boundary (Rectangle p r) -> Intersection (Line 2 r) (Boundary (Rectangle p r)) Source #

intersects :: Line 2 r -> Boundary (Rectangle p r) -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Boundary (Rectangle p r)) -> Intersection (Line 2 r) (Boundary (Rectangle p r)) -> Bool Source #

(Eq r, Fractional r) => IsIntersectableWith (Line 2 r) (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.Line.Internal

Methods

intersect :: Line 2 r -> Line 2 r -> Intersection (Line 2 r) (Line 2 r) Source #

intersects :: Line 2 r -> Line 2 r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Line 2 r) -> Intersection (Line 2 r) (Line 2 r) -> Bool Source #

(Ord r, Fractional r) => IsIntersectableWith (Line 2 r) (Rectangle p r) Source # 
Instance details

Defined in Data.Geometry.Line

Methods

intersect :: Line 2 r -> Rectangle p r -> Intersection (Line 2 r) (Rectangle p r) Source #

intersects :: Line 2 r -> Rectangle p r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Rectangle p r) -> Intersection (Line 2 r) (Rectangle p r) -> Bool Source #

(Ord r, Floating r) => IsIntersectableWith (Line 2 r) (Circle p r) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

intersect :: Line 2 r -> Circle p r -> Intersection (Line 2 r) (Circle p r) Source #

intersects :: Line 2 r -> Circle p r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Circle p r) -> Intersection (Line 2 r) (Circle p r) -> Bool Source #

Ord r => IsIntersectableWith (Interval a r) (Interval a r) Source # 
Instance details

Defined in Data.Geometry.Interval

Methods

intersect :: Interval a r -> Interval a r -> Intersection (Interval a r) (Interval a r) Source #

intersects :: Interval a r -> Interval a r -> Bool Source #

nonEmptyIntersection :: proxy (Interval a r) -> proxy (Interval a r) -> Intersection (Interval a r) (Interval a r) -> Bool Source #

(Arity d, Ord r) => IsIntersectableWith (Point d r) (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

intersect :: Point d r -> Box d p r -> Intersection (Point d r) (Box d p r) Source #

intersects :: Point d r -> Box d p r -> Bool Source #

nonEmptyIntersection :: proxy (Point d r) -> proxy (Box d p r) -> Intersection (Point d r) (Box d p r) -> Bool Source #

(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (Line 2 r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

intersect :: Line 2 r -> Slab o a r -> Intersection (Line 2 r) (Slab o a r) Source #

intersects :: Line 2 r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Slab o a r) -> Intersection (Line 2 r) (Slab o a r) -> Bool Source #

(Ord r, Fractional r) => IsIntersectableWith (LineSegment 2 p r) (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.LineSegment

Methods

intersect :: LineSegment 2 p r -> Line 2 r -> Intersection (LineSegment 2 p r) (Line 2 r) Source #

intersects :: LineSegment 2 p r -> Line 2 r -> Bool Source #

nonEmptyIntersection :: proxy (LineSegment 2 p r) -> proxy (Line 2 r) -> Intersection (LineSegment 2 p r) (Line 2 r) -> Bool Source #

(Ord r, Floating r) => IsIntersectableWith (LineSegment 2 p r) (Circle q r) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

intersect :: LineSegment 2 p r -> Circle q r -> Intersection (LineSegment 2 p r) (Circle q r) Source #

intersects :: LineSegment 2 p r -> Circle q r -> Bool Source #

nonEmptyIntersection :: proxy (LineSegment 2 p r) -> proxy (Circle q r) -> Intersection (LineSegment 2 p r) (Circle q r) -> Bool Source #

(Ord r, Arity d) => IsIntersectableWith (Box d p r) (Box d q r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

intersect :: Box d p r -> Box d q r -> Intersection (Box d p r) (Box d q r) Source #

intersects :: Box d p r -> Box d q r -> Bool Source #

nonEmptyIntersection :: proxy (Box d p r) -> proxy (Box d q r) -> Intersection (Box d p r) (Box d q r) -> Bool Source #

(Ord r, Fractional r) => IsIntersectableWith (SubLine 2 p r) (SubLine 2 p r) Source # 
Instance details

Defined in Data.Geometry.SubLine

Methods

intersect :: SubLine 2 p r -> SubLine 2 p r -> Intersection (SubLine 2 p r) (SubLine 2 p r) Source #

intersects :: SubLine 2 p r -> SubLine 2 p r -> Bool Source #

nonEmptyIntersection :: proxy (SubLine 2 p r) -> proxy (SubLine 2 p r) -> Intersection (SubLine 2 p r) (SubLine 2 p r) -> Bool Source #

(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (SubLine 2 a r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

intersect :: SubLine 2 a r -> Slab o a r -> Intersection (SubLine 2 a r) (Slab o a r) Source #

intersects :: SubLine 2 a r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (SubLine 2 a r) -> proxy (Slab o a r) -> Intersection (SubLine 2 a r) (Slab o a r) -> Bool Source #

(Ord r, Fractional r) => IsIntersectableWith (LineSegment 2 p r) (LineSegment 2 p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment

Methods

intersect :: LineSegment 2 p r -> LineSegment 2 p r -> Intersection (LineSegment 2 p r) (LineSegment 2 p r) Source #

intersects :: LineSegment 2 p r -> LineSegment 2 p r -> Bool Source #

nonEmptyIntersection :: proxy (LineSegment 2 p r) -> proxy (LineSegment 2 p r) -> Intersection (LineSegment 2 p r) (LineSegment 2 p r) -> Bool Source #

(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (LineSegment 2 a r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

intersect :: LineSegment 2 a r -> Slab o a r -> Intersection (LineSegment 2 a r) (Slab o a r) Source #

intersects :: LineSegment 2 a r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (LineSegment 2 a r) -> proxy (Slab o a r) -> Intersection (LineSegment 2 a r) (Slab o a r) -> Bool Source #

Ord r => IsIntersectableWith (Slab o a r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

intersect :: Slab o a r -> Slab o a r -> Intersection (Slab o a r) (Slab o a r) Source #

intersects :: Slab o a r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (Slab o a r) -> proxy (Slab o a r) -> Intersection (Slab o a r) (Slab o a r) -> Bool Source #

IsIntersectableWith (Slab Horizontal a r) (Slab Vertical a r) Source # 
Instance details

Defined in Data.Geometry.Slab

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

type family Union g h :: * Source #

class IsUnionableWith g h where Source #

Minimal complete definition

union

Methods

union :: g -> h -> Union g h Source #