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

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.PolyLine

Contents

Synopsis

d-dimensional Polygonal Lines (PolyLines)

newtype PolyLine d p r Source #

A Poly line in R^d has at least 2 vertices

Constructors

PolyLine 

Fields

Instances
Arity d => Bifunctor (PolyLine d) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

bimap :: (a -> b) -> (c -> d0) -> PolyLine d a c -> PolyLine d b d0 #

first :: (a -> b) -> PolyLine d a c -> PolyLine d b c #

second :: (b -> c) -> PolyLine d a b -> PolyLine d a c #

Arity d => Functor (PolyLine d p) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

fmap :: (a -> b) -> PolyLine d p a -> PolyLine d p b #

(<$) :: a -> PolyLine d p b -> PolyLine d p a #

PointFunctor (PolyLine d p) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

pmap :: (Point (Dimension (PolyLine d p r)) r -> Point (Dimension (PolyLine d p s)) s) -> PolyLine d p r -> PolyLine d p s Source #

(Eq r, Eq p, Arity d) => Eq (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

(==) :: PolyLine d p r -> PolyLine d p r -> Bool #

(/=) :: PolyLine d p r -> PolyLine d p r -> Bool #

(Ord r, Ord p, Arity d) => Ord (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

compare :: PolyLine d p r -> PolyLine d p r -> Ordering #

(<) :: PolyLine d p r -> PolyLine d p r -> Bool #

(<=) :: PolyLine d p r -> PolyLine d p r -> Bool #

(>) :: PolyLine d p r -> PolyLine d p r -> Bool #

(>=) :: PolyLine d p r -> PolyLine d p r -> Bool #

max :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r #

min :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r #

(Show r, Show p, Arity d) => Show (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

showsPrec :: Int -> PolyLine d p r -> ShowS #

show :: PolyLine d p r -> String #

showList :: [PolyLine d p r] -> ShowS #

Semigroup (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

(<>) :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r #

sconcat :: NonEmpty (PolyLine d p r) -> PolyLine d p r #

stimes :: Integral b => b -> PolyLine d p r -> PolyLine d p r #

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

transformBy :: Transformation (Dimension (PolyLine d p r)) (NumType (PolyLine d p r)) -> PolyLine d p r -> PolyLine d p r Source #

Arity d => IsBoxable (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

boundingBox :: PolyLine d p r -> Box (Dimension (PolyLine d p r)) () (NumType (PolyLine d p r)) Source #

(IpeWriteText r, IpeWrite p) => IpeWrite (PolyLine 2 p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

Methods

ipeWrite :: PolyLine 2 p r -> Maybe (Node Text Text) Source #

IpeWriteText r => IpeWriteText (PolyLine 2 () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

Methods

ipeWriteText :: PolyLine 2 () r -> Maybe Text Source #

HasDefaultFromIpe (PolyLine 2 () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (PolyLine 2 () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (PolyLine 2 () r) => Prism' (IpeObject r0) (PolyLine 2 () r :+ IpeAttributes (DefaultFromIpe (PolyLine 2 () r)) r0) Source #

HasDefaultIpeOut (PolyLine 2 p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (PolyLine 2 p r) :: Type -> Type Source #

Methods

defIO :: IpeOut (PolyLine 2 p r) (DefaultIpeOut (PolyLine 2 p r)) (NumType (PolyLine 2 p r)) Source #

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

Defined in Data.Geometry.PolyLine

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

Defined in Data.Geometry.PolyLine

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

Defined in Data.Geometry.Ipe.FromIpe

type DefaultFromIpe (PolyLine 2 () r) = Path
type DefaultIpeOut (PolyLine 2 p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

type DefaultIpeOut (PolyLine 2 p r) = Path

points :: forall d p r d p r. Iso (PolyLine d p r) (PolyLine d p r) (LSeq 2 ((:+) (Point d r) p)) (LSeq 2 ((:+) (Point d r) p)) Source #

fromPoints :: [Point d r :+ p] -> PolyLine d p r Source #

pre: The input list contains at least two points

fromPoints' :: Monoid p => [Point d r] -> PolyLine d p r Source #

pre: The input list contains at least two points. All extra vields are initialized with mempty.

fromLineSegment :: LineSegment d p r -> PolyLine d p r Source #

We consider the line-segment as closed.

asLineSegment :: PolyLine d p r -> LineSegment d p r Source #

Convert to a closed line segment by taking the first two points.

asLineSegment' :: PolyLine d p r -> Maybe (LineSegment d p r) Source #

Stricter version of asLineSegment that fails if the Polyline contains more than two points.