hgeometry-0.12.0.4: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.PolyLine

Description

 
Synopsis

Documentation

>>> :{
let myPolyLine = fromPointsUnsafe $ map ext [origin, Point2 10.0 10.0, Point2 10.0 20.0]
:}

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

Instances details
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 => Bitraversable (PolyLine d) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d0) -> PolyLine d a b -> f (PolyLine d c d0) #

Arity d => Bifoldable (PolyLine d) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

bifold :: Monoid m => PolyLine d m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> PolyLine d a b -> m #

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

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> PolyLine d a b -> 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 #

Generic (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Associated Types

type Rep (PolyLine d p r) :: Type -> Type #

Methods

from :: PolyLine d p r -> Rep (PolyLine d p r) x #

to :: Rep (PolyLine d p r) x -> PolyLine d p r #

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 #

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

Defined in Data.Geometry.PolyLine

Methods

toJSON :: PolyLine d p r -> Value #

toEncoding :: PolyLine d p r -> Encoding #

toJSONList :: [PolyLine d p r] -> Value #

toEncodingList :: [PolyLine d p r] -> Encoding #

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

Defined in Data.Geometry.PolyLine

Methods

parseJSON :: Value -> Parser (PolyLine d p r) #

parseJSONList :: Value -> Parser [PolyLine d p r] #

HasEnd (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Associated Types

type EndCore (PolyLine d p r) Source #

type EndExtra (PolyLine d p r) Source #

Methods

end :: Lens' (PolyLine d p r) (EndCore (PolyLine d p r) :+ EndExtra (PolyLine d p r)) Source #

HasStart (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Associated Types

type StartCore (PolyLine d p r) Source #

type StartExtra (PolyLine d p r) Source #

Methods

start :: Lens' (PolyLine d p r) (StartCore (PolyLine d p r) :+ StartExtra (PolyLine d p r)) Source #

(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 #

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

Defined in Data.Geometry.PolyLine

type Rep (PolyLine d p r) = D1 ('MetaData "PolyLine" "Data.Geometry.PolyLine" "hgeometry-0.12.0.4-4wzlMfvn1ROGs9ccdWmQbR" 'True) (C1 ('MetaCons "PolyLine" 'PrefixI 'True) (S1 ('MetaSel ('Just "_points") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LSeq 2 (Point d r :+ p)))))
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 EndCore (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type EndCore (PolyLine d p r) = Point d r
type EndExtra (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type EndExtra (PolyLine d p r) = p
type StartCore (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type StartCore (PolyLine d p r) = Point d r
type StartExtra (PolyLine d p r) Source # 
Instance details

Defined in Data.Geometry.PolyLine

type StartExtra (PolyLine d p r) = p

points :: Iso (PolyLine d1 p1 r1) (PolyLine d2 p2 r2) (LSeq 2 (Point d1 r1 :+ p1)) (LSeq 2 (Point d2 r2 :+ p2)) Source #

PolyLines are isomorphic to a sequence of points with at least 2 members.

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

Builds a Polyline from a list of points, if there are sufficiently many points

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

pre: The input list contains at least two points

fromPointsUnsafe' :: 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.

edgeSegments :: Arity d => PolyLine d p r -> LSeq 1 (LineSegment d p r) Source #

Computes the edges, as linesegments, of an LSeq

interpolatePoly :: (RealFrac r, Arity d) => r -> PolyLine d p r -> Point d r Source #

Linearly interpolate the polyline with a value in the range \([0,n-1]\), where \(n\) is the number of vertices of the polyline.

running time: \(O(\log n)\)

>>> interpolatePoly 0.5 myPolyLine
Point2 5.0 5.0
>>> interpolatePoly 1.5 myPolyLine
Point2 10.0 15.0