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

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.PlanarSubdivision.Basic

Description

Description : Basic data types to represent a PlanarSubdivision

Synopsis

Documentation

type VertexId' s = VertexId s Primal Source #

Shorthand for vertices in the primal.

type FaceId' s = FaceId s Primal Source #

Shorthand for FaceId's in the primal.

data VertexData r v Source #

Note that the functor instance is in v

Constructors

VertexData !(Point 2 r) !v 
Instances
Bifunctor VertexData Source # 
Instance details

Defined in Data.PlaneGraph

Methods

bimap :: (a -> b) -> (c -> d) -> VertexData a c -> VertexData b d #

first :: (a -> b) -> VertexData a c -> VertexData b c #

second :: (b -> c) -> VertexData a b -> VertexData a c #

Functor (VertexData r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

fmap :: (a -> b) -> VertexData r a -> VertexData r b #

(<$) :: a -> VertexData r b -> VertexData r a #

Foldable (VertexData r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

fold :: Monoid m => VertexData r m -> m #

foldMap :: Monoid m => (a -> m) -> VertexData r a -> m #

foldr :: (a -> b -> b) -> b -> VertexData r a -> b #

foldr' :: (a -> b -> b) -> b -> VertexData r a -> b #

foldl :: (b -> a -> b) -> b -> VertexData r a -> b #

foldl' :: (b -> a -> b) -> b -> VertexData r a -> b #

foldr1 :: (a -> a -> a) -> VertexData r a -> a #

foldl1 :: (a -> a -> a) -> VertexData r a -> a #

toList :: VertexData r a -> [a] #

null :: VertexData r a -> Bool #

length :: VertexData r a -> Int #

elem :: Eq a => a -> VertexData r a -> Bool #

maximum :: Ord a => VertexData r a -> a #

minimum :: Ord a => VertexData r a -> a #

sum :: Num a => VertexData r a -> a #

product :: Num a => VertexData r a -> a #

Traversable (VertexData r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

traverse :: Applicative f => (a -> f b) -> VertexData r a -> f (VertexData r b) #

sequenceA :: Applicative f => VertexData r (f a) -> f (VertexData r a) #

mapM :: Monad m => (a -> m b) -> VertexData r a -> m (VertexData r b) #

sequence :: Monad m => VertexData r (m a) -> m (VertexData r a) #

(Eq r, Eq v) => Eq (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

(==) :: VertexData r v -> VertexData r v -> Bool #

(/=) :: VertexData r v -> VertexData r v -> Bool #

(Ord r, Ord v) => Ord (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

compare :: VertexData r v -> VertexData r v -> Ordering #

(<) :: VertexData r v -> VertexData r v -> Bool #

(<=) :: VertexData r v -> VertexData r v -> Bool #

(>) :: VertexData r v -> VertexData r v -> Bool #

(>=) :: VertexData r v -> VertexData r v -> Bool #

max :: VertexData r v -> VertexData r v -> VertexData r v #

min :: VertexData r v -> VertexData r v -> VertexData r v #

(Show r, Show v) => Show (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

showsPrec :: Int -> VertexData r v -> ShowS #

show :: VertexData r v -> String #

showList :: [VertexData r v] -> ShowS #

Generic (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type Rep (VertexData r v) :: Type -> Type #

Methods

from :: VertexData r v -> Rep (VertexData r v) x #

to :: Rep (VertexData r v) x -> VertexData r v #

(ToJSON r, ToJSON v) => ToJSON (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

(FromJSON r, FromJSON v) => FromJSON (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

type Rep (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph

type Rep (VertexData r v) = D1 (MetaData "VertexData" "Data.PlaneGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "VertexData" PrefixI True) (S1 (MetaSel (Just "_location") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Point 2 r)) :*: S1 (MetaSel (Just "_vData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 v)))

vData :: forall r v v. Lens (VertexData r v) (VertexData r v) v v Source #

location :: forall r v r. Lens (VertexData r v) (VertexData r v) (Point 2 r) (Point 2 r) Source #

data FaceData h f Source #

The Face data consists of the data itself and a list of holes

Constructors

FaceData (Seq h) !f 
Instances
Bifunctor FaceData Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

bimap :: (a -> b) -> (c -> d) -> FaceData a c -> FaceData b d #

first :: (a -> b) -> FaceData a c -> FaceData b c #

second :: (b -> c) -> FaceData a b -> FaceData a c #

Functor (FaceData h) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

fmap :: (a -> b) -> FaceData h a -> FaceData h b #

(<$) :: a -> FaceData h b -> FaceData h a #

Foldable (FaceData h) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

fold :: Monoid m => FaceData h m -> m #

foldMap :: Monoid m => (a -> m) -> FaceData h a -> m #

foldr :: (a -> b -> b) -> b -> FaceData h a -> b #

foldr' :: (a -> b -> b) -> b -> FaceData h a -> b #

foldl :: (b -> a -> b) -> b -> FaceData h a -> b #

foldl' :: (b -> a -> b) -> b -> FaceData h a -> b #

foldr1 :: (a -> a -> a) -> FaceData h a -> a #

foldl1 :: (a -> a -> a) -> FaceData h a -> a #

toList :: FaceData h a -> [a] #

null :: FaceData h a -> Bool #

length :: FaceData h a -> Int #

elem :: Eq a => a -> FaceData h a -> Bool #

maximum :: Ord a => FaceData h a -> a #

minimum :: Ord a => FaceData h a -> a #

sum :: Num a => FaceData h a -> a #

product :: Num a => FaceData h a -> a #

Traversable (FaceData h) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

traverse :: Applicative f => (a -> f b) -> FaceData h a -> f (FaceData h b) #

sequenceA :: Applicative f => FaceData h (f a) -> f (FaceData h a) #

mapM :: Monad m => (a -> m b) -> FaceData h a -> m (FaceData h b) #

sequence :: Monad m => FaceData h (m a) -> m (FaceData h a) #

(Eq h, Eq f) => Eq (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

(==) :: FaceData h f -> FaceData h f -> Bool #

(/=) :: FaceData h f -> FaceData h f -> Bool #

(Ord h, Ord f) => Ord (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

compare :: FaceData h f -> FaceData h f -> Ordering #

(<) :: FaceData h f -> FaceData h f -> Bool #

(<=) :: FaceData h f -> FaceData h f -> Bool #

(>) :: FaceData h f -> FaceData h f -> Bool #

(>=) :: FaceData h f -> FaceData h f -> Bool #

max :: FaceData h f -> FaceData h f -> FaceData h f #

min :: FaceData h f -> FaceData h f -> FaceData h f #

(Show h, Show f) => Show (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

showsPrec :: Int -> FaceData h f -> ShowS #

show :: FaceData h f -> String #

showList :: [FaceData h f] -> ShowS #

Generic (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type Rep (FaceData h f) :: Type -> Type #

Methods

from :: FaceData h f -> Rep (FaceData h f) x #

to :: Rep (FaceData h f) x -> FaceData h f #

(ToJSON h, ToJSON f) => ToJSON (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

(FromJSON h, FromJSON f) => FromJSON (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Rep (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Rep (FaceData h f) = D1 (MetaData "FaceData" "Data.Geometry.PlanarSubdivision.Basic" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "FaceData" PrefixI True) (S1 (MetaSel (Just "_holes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq h)) :*: S1 (MetaSel (Just "_fData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 f)))

holes :: forall h f h. Lens (FaceData h f) (FaceData h f) (Seq h) (Seq h) Source #

fData :: forall h f f. Lens (FaceData h f) (FaceData h f) f f Source #

data PlanarSubdivision s v e f r Source #

A planarsubdivision is essentially a bunch of plane-graphs; one for every connected component. These graphs store the global ID's (darts, vertexId's, faceId's) in their data values. This essentially gives us a mapping between the two.

note that a face may actually occur in multiple graphs, hence when we store the edges to the the holes, we store the global edgeId's rather than the local edgeId (dart)'s.

invariant: the outerface has faceId 0

Constructors

PlanarSubdivision (Vector (Component s r)) (Vector (Raw s (VertexId' (Wrap s)) v)) (Vector (Raw s (Dart (Wrap s)) e)) (Vector (Raw s (FaceId' (Wrap s)) f)) 
Instances
Functor (PlanarSubdivision s v e f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

fmap :: (a -> b) -> PlanarSubdivision s v e f a -> PlanarSubdivision s v e f b #

(<$) :: a -> PlanarSubdivision s v e f b -> PlanarSubdivision s v e f a #

(Eq r, Eq v, Eq e, Eq f) => Eq (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

(==) :: PlanarSubdivision s v e f r -> PlanarSubdivision s v e f r -> Bool #

(/=) :: PlanarSubdivision s v e f r -> PlanarSubdivision s v e f r -> Bool #

(Show r, Show v, Show e, Show f) => Show (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

showsPrec :: Int -> PlanarSubdivision s v e f r -> ShowS #

show :: PlanarSubdivision s v e f r -> String #

showList :: [PlanarSubdivision s v e f r] -> ShowS #

Generic (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type Rep (PlanarSubdivision s v e f r) :: Type -> Type #

Methods

from :: PlanarSubdivision s v e f r -> Rep (PlanarSubdivision s v e f r) x #

to :: Rep (PlanarSubdivision s v e f r) x -> PlanarSubdivision s v e f r #

IsBoxable (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

boundingBox :: PlanarSubdivision s v e f r -> Box (Dimension (PlanarSubdivision s v e f r)) () (NumType (PlanarSubdivision s v e f r)) Source #

HasDataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) :: Type Source #

Methods

dataOf :: FaceId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (FaceId' s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (Dart s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) :: Type Source #

Methods

dataOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (VertexId' s)) Source #

type Rep (PlanarSubdivision s v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Rep (PlanarSubdivision s v e f r) = D1 (MetaData "PlanarSubdivision" "Data.Geometry.PlanarSubdivision.Basic" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "PlanarSubdivision" PrefixI True) ((S1 (MetaSel (Just "_components") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Component s r))) :*: S1 (MetaSel (Just "_rawVertexData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Raw s (VertexId' (Wrap s)) v)))) :*: (S1 (MetaSel (Just "_rawDartData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Raw s (Dart (Wrap s)) e))) :*: S1 (MetaSel (Just "_rawFaceData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Raw s (FaceId' (Wrap s)) f))))))
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 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 DataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) = f
type DataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (Dart s) = e
type DataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) = v

type family Wrap (s :: k) :: k where ... Source #

Equations

Wrap s = Wrap' s 

type Component s r = PlaneGraph (Wrap s) (VertexId' s) (Dart s) (FaceData (Dart s) (FaceId' s)) r Source #

A connected component.

For every face f, and every hole in this face, the facedata points to a dart d on the hole s.t. this dart has the face f on its left. i.e. leftFace d = f

data ComponentId s Source #

Instances
Bounded (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Enum (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Eq (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Ord (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Show (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Generic (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type Rep (ComponentId s) :: Type -> Type #

Methods

from :: ComponentId s -> Rep (ComponentId s) x #

to :: Rep (ComponentId s) x -> ComponentId s #

ToJSON (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

FromJSON (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Rep (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Rep (ComponentId s) = D1 (MetaData "ComponentId" "Data.Geometry.PlanarSubdivision.Basic" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" True) (C1 (MetaCons "ComponentId" PrefixI True) (S1 (MetaSel (Just "unCI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data PlanarGraph s (w :: World) v e f Source #

A *connected* Planar graph with bidirected edges. I.e. the edges (darts) are directed, however, for every directed edge, the edge in the oposite direction is also in the graph.

The types v, e, and f are the are the types of the data associated with the vertices, edges, and faces, respectively.

The orbits in the embedding are assumed to be in counterclockwise order. Therefore, every dart directly bounds the face to its right.

Instances
(Eq v, Eq e, Eq f) => Eq (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

(==) :: PlanarGraph s w v e f -> PlanarGraph s w v e f -> Bool #

(/=) :: PlanarGraph s w v e f -> PlanarGraph s w v e f -> Bool #

(Show v, Show e, Show f) => Show (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> PlanarGraph s w v e f -> ShowS #

show :: PlanarGraph s w v e f -> String #

showList :: [PlanarGraph s w v e f] -> ShowS #

Generic (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type Rep (PlanarGraph s w v e f) :: Type -> Type #

Methods

from :: PlanarGraph s w v e f -> Rep (PlanarGraph s w v e f) x #

to :: Rep (PlanarGraph s w v e f) x -> PlanarGraph s w v e f #

(ToJSON v, ToJSON e, ToJSON f) => ToJSON (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

toJSON :: PlanarGraph s w v e f -> Value #

toEncoding :: PlanarGraph s w v e f -> Encoding #

toJSONList :: [PlanarGraph s w v e f] -> Value #

toEncodingList :: [PlanarGraph s w v e f] -> Encoding #

(FromJSON v, FromJSON e, FromJSON f) => FromJSON (PlanarGraph s Primal v e f) Source # 
Instance details

Defined in Data.PlanarGraph

HasDataOf (PlanarGraph s w v e f) (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source #

HasDataOf (PlanarGraph s w v e f) (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (VertexId s w) :: Type Source #

Methods

dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) Source #

HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (FaceId s w) :: Type Source #

Methods

dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source #

type Rep (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

type Rep (PlanarGraph s w v e f) = D1 (MetaData "PlanarGraph" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "PlanarGraph" PrefixI True) ((S1 (MetaSel (Just "_embedding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Permutation (Dart s))) :*: S1 (MetaSel (Just "_vertexData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector v))) :*: (S1 (MetaSel (Just "_rawDartData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector e)) :*: (S1 (MetaSel (Just "_faceData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector f)) :*: S1 (MetaSel (Just "_dual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PlanarGraph s (DualOf w) f e v))))))
type DataOf (PlanarGraph s w v e f) (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

type DataOf (PlanarGraph s w v e f) (Dart s) = e
type DataOf (PlanarGraph s w v e f) (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

type DataOf (PlanarGraph s w v e f) (VertexId s w) = v
type DataOf (PlanarGraph s w v e f) (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

type DataOf (PlanarGraph s w v e f) (FaceId s w) = f

data PlaneGraph s v e f r Source #

Embedded, *connected*, planar graph

Instances
Functor (PlaneGraph s v e f) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

fmap :: (a -> b) -> PlaneGraph s v e f a -> PlaneGraph s v e f b #

(<$) :: a -> PlaneGraph s v e f b -> PlaneGraph s v e f a #

(Eq r, Eq v, Eq e, Eq f) => Eq (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

(==) :: PlaneGraph s v e f r -> PlaneGraph s v e f r -> Bool #

(/=) :: PlaneGraph s v e f r -> PlaneGraph s v e f r -> Bool #

(Show r, Show v, Show e, Show f) => Show (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

showsPrec :: Int -> PlaneGraph s v e f r -> ShowS #

show :: PlaneGraph s v e f r -> String #

showList :: [PlaneGraph s v e f r] -> ShowS #

Generic (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type Rep (PlaneGraph s v e f r) :: Type -> Type #

Methods

from :: PlaneGraph s v e f r -> Rep (PlaneGraph s v e f r) x #

to :: Rep (PlaneGraph s v e f r) x -> PlaneGraph s v e f r #

(ToJSON r, ToJSON v, ToJSON e, ToJSON f) => ToJSON (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

toJSON :: PlaneGraph s v e f r -> Value #

toEncoding :: PlaneGraph s v e f r -> Encoding #

toJSONList :: [PlaneGraph s v e f r] -> Value #

toEncodingList :: [PlaneGraph s v e f r] -> Encoding #

(FromJSON r, FromJSON v, FromJSON e, FromJSON f) => FromJSON (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

parseJSON :: Value -> Parser (PlaneGraph s v e f r) #

parseJSONList :: Value -> Parser [PlaneGraph s v e f r] #

IsBoxable (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

Methods

boundingBox :: PlaneGraph s v e f r -> Box (Dimension (PlaneGraph s v e f r)) () (NumType (PlaneGraph s v e f r)) Source #

HasDataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) :: Type Source #

Methods

dataOf :: FaceId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (FaceId' s)) Source #

HasDataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) Source #

HasDataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (VertexId' s) :: Type Source #

Methods

dataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (VertexId' s)) Source #

type Rep (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

type Rep (PlaneGraph s v e f r) = D1 (MetaData "PlaneGraph" "Data.PlaneGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" True) (C1 (MetaCons "PlaneGraph" PrefixI True) (S1 (MetaSel (Just "_graph") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PlanarGraph s Primal (VertexData r v) e f))))
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 Dimension (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

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

Defined in Data.PlaneGraph

type DataOf (PlaneGraph s v e f r) (FaceId' s) = f
type DataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph

type DataOf (PlaneGraph s v e f r) (Dart s) = e
type DataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph

type DataOf (PlaneGraph s v e f r) (VertexId' s) = v

fromSimplePolygon Source #

Arguments

:: (Ord r, Fractional r) 
=> proxy s 
-> SimplePolygon p r 
-> f

data inside

-> f

data outside the polygon

-> PlanarSubdivision s p () f r 

Construct a planar subdivision from a simple polygon

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

fromConnectedSegments :: (Foldable f, Ord r, Fractional r) => proxy s -> f (LineSegment 2 p r :+ e) -> PlanarSubdivision s (NonEmpty p) e () r Source #

Constructs a connected planar subdivision.

pre: the segments form a single connected component running time: \(O(n\log n)\)

fromPlaneGraph :: forall s v e f r. (Ord r, Fractional r) => PlaneGraph s v e f r -> PlanarSubdivision s v e f r Source #

Constructs a planarsubdivision from a PlaneGraph

runningTime: \(O(n)\)

fromPlaneGraph' :: forall s v e f r. PlaneGraph s v e f r -> Dart s -> PlanarSubdivision s v e f r Source #

Given a (connected) PlaneGraph and a dart that has the outerface on its left | Constructs a planarsubdivision

runningTime: \(O(n)\)

numVertices :: PlanarSubdivision s v e f r -> Int Source #

Get the number of vertices

>>> numVertices myGraph
4

numEdges :: PlanarSubdivision s v e f r -> Int Source #

Get the number of Edges

>>> numEdges myGraph
6

numFaces :: PlanarSubdivision s v e f r -> Int Source #

Get the number of faces

>>> numFaces myGraph
4

numDarts :: PlanarSubdivision s v e f r -> Int Source #

Get the number of Darts

>>> numDarts myGraph
12

dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v) Source #

Get the dual graph of this graph.

components :: forall s v e f r r. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Component s r)) (Vector (Component s r)) Source #

vertices' :: PlanarSubdivision s v e f r -> Vector (VertexId' s) Source #

Enumerate all vertices

>>> vertices' myGraph
[VertexId 0,VertexId 1,VertexId 2,VertexId 3]

vertices :: PlanarSubdivision s v e f r -> Vector (VertexId' s, VertexData r v) Source #

Enumerate all vertices, together with their vertex data

edges' :: PlanarSubdivision s v e f r -> Vector (Dart s) Source #

Enumerate all edges. We report only the Positive darts

edges :: PlanarSubdivision s v e f r -> Vector (Dart s, e) Source #

Enumerate all edges with their edge data. We report only the Positive darts.

>>> mapM_ print $ edges myGraph
(Dart (Arc 2) +1,"c+")
(Dart (Arc 1) +1,"b+")
(Dart (Arc 0) +1,"a+")
(Dart (Arc 5) +1,"g+")
(Dart (Arc 4) +1,"e+")
(Dart (Arc 3) +1,"d+")

internalFaces :: (Ord r, Fractional r) => PlanarSubdivision s v e f r -> Vector (FaceId' s, FaceData (Dart s) f) Source #

Enumerates all faces with their face data exlcluding the outer face

darts' :: PlanarSubdivision s v e f r -> Vector (Dart s) Source #

Enumerate all darts

headOf :: Dart s -> PlanarSubdivision s v e f r -> VertexId' s Source #

The vertex this dart is heading in to

running time: \(O(1)\)

tailOf :: Dart s -> PlanarSubdivision s v e f r -> VertexId' s Source #

The tail of a dart, i.e. the vertex this dart is leaving from

running time: \(O(1)\)

twin :: Dart s -> Dart s Source #

Get the twin of this dart (edge)

>>> twin (dart 0 "+1")
Dart (Arc 0) -1
>>> twin (dart 0 "-1")
Dart (Arc 0) +1

endPoints :: Dart s -> PlanarSubdivision s v e f r -> (VertexId' s, VertexId' s) Source #

endPoints d g = (tailOf d g, headOf d g)

running time: \(O(1)\)

incidentEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #

All edges incident to vertex v, in counterclockwise order around v.

running time: \(O(k)\), where \(k\) is the number of edges reported.

incomingEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #

All incoming edges incident to vertex v, in counterclockwise order around v.

outgoingEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #

All outgoing edges incident to vertex v, in counterclockwise order around v.

nextIncidentEdge :: Dart s -> PlanarSubdivision s v e f r -> Dart s Source #

Given a dart d that points into some vertex v, report the next dart e in the cyclic order around v.

running time: \(O(1)\)

neighboursOf :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (VertexId' s) Source #

Gets the neighbours of a particular vertex, in counterclockwise order around the vertex.

running time: \(O(k)\), where \(k\) is the output size

leftFace :: Dart s -> PlanarSubdivision s v e f r -> FaceId' s Source #

The face to the left of the dart

running time: \(O(1)\).

rightFace :: Dart s -> PlanarSubdivision s v e f r -> FaceId' s Source #

The face to the right of the dart

running time: \(O(1)\).

outerBoundaryDarts :: FaceId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #

The darts on the outer boundary of the face, for internal faces in clockwise order, for the outer face in counter clockwise order.

running time: \(O(k)\), where \(k\) is the output size.

boundaryVertices :: FaceId' s -> PlanarSubdivision s v e f r -> Vector (VertexId' s) Source #

The vertices of the outer boundary of the face, for internal faces in clockwise order, for the outer face in counter clockwise order.

running time: \(O(k)\), where \(k\) is the output size.

holesOf :: FaceId' s -> PlanarSubdivision s v e f r -> Seq (Dart s) Source #

Lists the holes in this face, given as a list of darts to arbitrary darts on those faces.

running time: \(O(k)\), where \(k\) is the number of darts returned.

outerFaceId :: PlanarSubdivision s v e f r -> FaceId' s Source #

gets the id of the outer face

running time: \(O(1)\)

boundary' :: Dart s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #

Generates the darts incident to a face, starting with the given dart.

\(O(k)\), where \(k\) is the number of darts reported

class HasDataOf g i where Source #

Associated Types

type DataOf g i Source #

Methods

dataOf :: i -> Lens' g (DataOf g i) Source #

get the data associated with the value i.

running time: \(O(1)\) to read the data, \(O(n)\) to write it.

Instances
HasDataOf (PlanarGraph s w v e f) (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source #

HasDataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) :: Type Source #

Methods

dataOf :: FaceId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (FaceId' s)) Source #

HasDataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) Source #

HasDataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (VertexId' s) :: Type Source #

Methods

dataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (VertexId' s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) :: Type Source #

Methods

dataOf :: FaceId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (FaceId' s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (Dart s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) :: Type Source #

Methods

dataOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (VertexId' s)) Source #

HasDataOf (PlanarGraph s w v e f) (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (VertexId s w) :: Type Source #

Methods

dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) Source #

HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (FaceId s w) :: Type Source #

Methods

dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source #

endPointsOf :: Dart s -> Getter (PlanarSubdivision s v e f r) (VertexData r v, VertexData r v) Source #

Getter for the data at the endpoints of a dart

running time: \(O(1)\)

endPointData :: Dart s -> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v) Source #

data corresponding to the endpoints of the dart

running time: \(O(1)\)

edgeSegment :: Dart s -> PlanarSubdivision s v e f r -> LineSegment 2 v r :+ e Source #

Given a dart and the subdivision constructs the line segment representing it

\(O(1)\)

edgeSegments :: PlanarSubdivision s v e f r -> Vector (Dart s, LineSegment 2 v r :+ e) Source #

Reports all edges as line segments

rawFacePolygon :: FaceId' s -> PlanarSubdivision s v e f r -> SomePolygon v r :+ f Source #

Constructs the boundary of the given face

\(O(k)\), where \(k\) is the complexity of the face

rawFaceBoundary :: FaceId' s -> PlanarSubdivision s v e f r -> SimplePolygon v r :+ f Source #

Constructs the outer boundary of the face

\(O(k)\), where \(k\) is the complexity of the outer boundary of the face

rawFacePolygons :: PlanarSubdivision s v e f r -> Vector (FaceId' s, SomePolygon v r :+ f) Source #

Lists all faces of the planar subdivision.

newtype VertexId s (w :: World) Source #

A vertex in a planar graph. A vertex is tied to a particular planar graph by the phantom type s, and to a particular world w.

Constructors

VertexId 

Fields

Instances
Enum (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

succ :: VertexId s w -> VertexId s w #

pred :: VertexId s w -> VertexId s w #

toEnum :: Int -> VertexId s w #

fromEnum :: VertexId s w -> Int #

enumFrom :: VertexId s w -> [VertexId s w] #

enumFromThen :: VertexId s w -> VertexId s w -> [VertexId s w] #

enumFromTo :: VertexId s w -> VertexId s w -> [VertexId s w] #

enumFromThenTo :: VertexId s w -> VertexId s w -> VertexId s w -> [VertexId s w] #

Eq (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

(==) :: VertexId s w -> VertexId s w -> Bool #

(/=) :: VertexId s w -> VertexId s w -> Bool #

Ord (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

compare :: VertexId s w -> VertexId s w -> Ordering #

(<) :: VertexId s w -> VertexId s w -> Bool #

(<=) :: VertexId s w -> VertexId s w -> Bool #

(>) :: VertexId s w -> VertexId s w -> Bool #

(>=) :: VertexId s w -> VertexId s w -> Bool #

max :: VertexId s w -> VertexId s w -> VertexId s w #

min :: VertexId s w -> VertexId s w -> VertexId s w #

Show (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> VertexId s w -> ShowS #

show :: VertexId s w -> String #

showList :: [VertexId s w] -> ShowS #

Generic (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type Rep (VertexId s w) :: Type -> Type #

Methods

from :: VertexId s w -> Rep (VertexId s w) x #

to :: Rep (VertexId s w) x -> VertexId s w #

ToJSON (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

FromJSON (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

NFData (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

rnf :: VertexId s w -> () #

HasDataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (VertexId' s) :: Type Source #

Methods

dataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (VertexId' s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) :: Type Source #

Methods

dataOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (VertexId' s)) Source #

HasDataOf (PlanarGraph s w v e f) (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (VertexId s w) :: Type Source #

Methods

dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) Source #

type Rep (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

type Rep (VertexId s w) = D1 (MetaData "VertexId" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" True) (C1 (MetaCons "VertexId" PrefixI True) (S1 (MetaSel (Just "_unVertexId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
type DataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph

type DataOf (PlaneGraph s v e f r) (VertexId' s) = v
type DataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) = v
type DataOf (PlanarGraph s w v e f) (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

type DataOf (PlanarGraph s w v e f) (VertexId s w) = v

newtype FaceId s w Source #

The type to reprsent FaceId's

Constructors

FaceId 

Fields

Instances
Enum (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

succ :: FaceId s w -> FaceId s w #

pred :: FaceId s w -> FaceId s w #

toEnum :: Int -> FaceId s w #

fromEnum :: FaceId s w -> Int #

enumFrom :: FaceId s w -> [FaceId s w] #

enumFromThen :: FaceId s w -> FaceId s w -> [FaceId s w] #

enumFromTo :: FaceId s w -> FaceId s w -> [FaceId s w] #

enumFromThenTo :: FaceId s w -> FaceId s w -> FaceId s w -> [FaceId s w] #

Eq (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

(==) :: FaceId s w -> FaceId s w -> Bool #

(/=) :: FaceId s w -> FaceId s w -> Bool #

Ord (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

compare :: FaceId s w -> FaceId s w -> Ordering #

(<) :: FaceId s w -> FaceId s w -> Bool #

(<=) :: FaceId s w -> FaceId s w -> Bool #

(>) :: FaceId s w -> FaceId s w -> Bool #

(>=) :: FaceId s w -> FaceId s w -> Bool #

max :: FaceId s w -> FaceId s w -> FaceId s w #

min :: FaceId s w -> FaceId s w -> FaceId s w #

Show (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> FaceId s w -> ShowS #

show :: FaceId s w -> String #

showList :: [FaceId s w] -> ShowS #

ToJSON (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

toJSON :: FaceId s w -> Value #

toEncoding :: FaceId s w -> Encoding #

toJSONList :: [FaceId s w] -> Value #

toEncodingList :: [FaceId s w] -> Encoding #

FromJSON (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

parseJSON :: Value -> Parser (FaceId s w) #

parseJSONList :: Value -> Parser [FaceId s w] #

HasDataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) :: Type Source #

Methods

dataOf :: FaceId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (FaceId' s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) :: Type Source #

Methods

dataOf :: FaceId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (FaceId' s)) Source #

HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (FaceId s w) :: Type Source #

Methods

dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source #

type DataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph

type DataOf (PlaneGraph s v e f r) (FaceId' s) = f
type DataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) = f
type DataOf (PlanarGraph s w v e f) (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

type DataOf (PlanarGraph s w v e f) (FaceId s w) = f

data Dart s Source #

A dart represents a bi-directed edge. I.e. a dart has a direction, however the dart of the oposite direction is always present in the planar graph as well.

Instances
Enum (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

succ :: Dart s -> Dart s #

pred :: Dart s -> Dart s #

toEnum :: Int -> Dart s #

fromEnum :: Dart s -> Int #

enumFrom :: Dart s -> [Dart s] #

enumFromThen :: Dart s -> Dart s -> [Dart s] #

enumFromTo :: Dart s -> Dart s -> [Dart s] #

enumFromThenTo :: Dart s -> Dart s -> Dart s -> [Dart s] #

Eq (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

(==) :: Dart s -> Dart s -> Bool #

(/=) :: Dart s -> Dart s -> Bool #

Ord (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

compare :: Dart s -> Dart s -> Ordering #

(<) :: Dart s -> Dart s -> Bool #

(<=) :: Dart s -> Dart s -> Bool #

(>) :: Dart s -> Dart s -> Bool #

(>=) :: Dart s -> Dart s -> Bool #

max :: Dart s -> Dart s -> Dart s #

min :: Dart s -> Dart s -> Dart s #

Show (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> Dart s -> ShowS #

show :: Dart s -> String #

showList :: [Dart s] -> ShowS #

Generic (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type Rep (Dart s) :: Type -> Type #

Methods

from :: Dart s -> Rep (Dart s) x #

to :: Rep (Dart s) x -> Dart s #

Arbitrary (Dart s) Source # 
Instance details

Defined in Test.QuickCheck.HGeometryInstances

Methods

arbitrary :: Gen (Dart s) #

shrink :: Dart s -> [Dart s] #

NFData (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

rnf :: Dart s -> () #

HasDataOf (PlanarGraph s w v e f) (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type DataOf (PlanarGraph s w v e f) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source #

HasDataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph

Associated Types

type DataOf (PlaneGraph s v e f r) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) Source #

HasDataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (Dart s) :: Type Source #

Methods

dataOf :: Dart s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (Dart s)) Source #

type Rep (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

type Rep (Dart s) = D1 (MetaData "Dart" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "Dart" PrefixI True) (S1 (MetaSel (Just "_arc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Arc s)) :*: S1 (MetaSel (Just "_direction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Direction)))
type DataOf (PlanarGraph s w v e f) (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

type DataOf (PlanarGraph s w v e f) (Dart s) = e
type DataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph

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

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (Dart s) = e

data World Source #

The world in which the graph lives

Constructors

Primal 
Dual 
Instances
Eq World Source # 
Instance details

Defined in Data.PlanarGraph

Methods

(==) :: World -> World -> Bool #

(/=) :: World -> World -> Bool #

Show World Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> World -> ShowS #

show :: World -> String #

showList :: [World] -> ShowS #

rawVertexData :: forall s v e f r v. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (VertexId' (Wrap s)) v)) (Vector (Raw s (VertexId' (Wrap s)) v)) Source #

rawDartData :: forall s v e f r e. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (Dart (Wrap s)) e)) (Vector (Raw s (Dart (Wrap s)) e)) Source #

rawFaceData :: forall s v e f r f. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (FaceId' (Wrap s)) f)) (Vector (Raw s (FaceId' (Wrap s)) f)) Source #

vertexData :: Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v' e f r) (Vector v) (Vector v') Source #

Lens to the facedata of the vertexdata themselves. The indices correspond to the vertexId's

dartData :: Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e' f r) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #

lens to access the Dart Data

faceData :: Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f' r) (Vector f) (Vector f') Source #

Lens to the facedata of the faces themselves. The indices correspond to the faceIds

dataVal :: Lens (Raw s ia a) (Raw s ia b) a b Source #

get the dataVal of a Raw

data Raw s ia a Source #

Constructors

Raw 

Fields

Instances
Functor (Raw s ia) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

fmap :: (a -> b) -> Raw s ia a -> Raw s ia b #

(<$) :: a -> Raw s ia b -> Raw s ia a #

Foldable (Raw s ia) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

fold :: Monoid m => Raw s ia m -> m #

foldMap :: Monoid m => (a -> m) -> Raw s ia a -> m #

foldr :: (a -> b -> b) -> b -> Raw s ia a -> b #

foldr' :: (a -> b -> b) -> b -> Raw s ia a -> b #

foldl :: (b -> a -> b) -> b -> Raw s ia a -> b #

foldl' :: (b -> a -> b) -> b -> Raw s ia a -> b #

foldr1 :: (a -> a -> a) -> Raw s ia a -> a #

foldl1 :: (a -> a -> a) -> Raw s ia a -> a #

toList :: Raw s ia a -> [a] #

null :: Raw s ia a -> Bool #

length :: Raw s ia a -> Int #

elem :: Eq a => a -> Raw s ia a -> Bool #

maximum :: Ord a => Raw s ia a -> a #

minimum :: Ord a => Raw s ia a -> a #

sum :: Num a => Raw s ia a -> a #

product :: Num a => Raw s ia a -> a #

Traversable (Raw s ia) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

traverse :: Applicative f => (a -> f b) -> Raw s ia a -> f (Raw s ia b) #

sequenceA :: Applicative f => Raw s ia (f a) -> f (Raw s ia a) #

mapM :: Monad m => (a -> m b) -> Raw s ia a -> m (Raw s ia b) #

sequence :: Monad m => Raw s ia (m a) -> m (Raw s ia a) #

(Eq ia, Eq a) => Eq (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

(==) :: Raw s ia a -> Raw s ia a -> Bool #

(/=) :: Raw s ia a -> Raw s ia a -> Bool #

(Show ia, Show a) => Show (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

showsPrec :: Int -> Raw s ia a -> ShowS #

show :: Raw s ia a -> String #

showList :: [Raw s ia a] -> ShowS #

Generic (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type Rep (Raw s ia a) :: Type -> Type #

Methods

from :: Raw s ia a -> Rep (Raw s ia a) x #

to :: Rep (Raw s ia a) x -> Raw s ia a #

(ToJSON ia, ToJSON a) => ToJSON (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

toJSON :: Raw s ia a -> Value #

toEncoding :: Raw s ia a -> Encoding #

toJSONList :: [Raw s ia a] -> Value #

toEncodingList :: [Raw s ia a] -> Encoding #

(FromJSON ia, FromJSON a) => FromJSON (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

parseJSON :: Value -> Parser (Raw s ia a) #

parseJSONList :: Value -> Parser [Raw s ia a] #

type Rep (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type Rep (Raw s ia a) = D1 (MetaData "Raw" "Data.Geometry.PlanarSubdivision.Basic" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "Raw" PrefixI True) (S1 (MetaSel (Just "_compId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (ComponentId s)) :*: (S1 (MetaSel (Just "_idxVal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ia) :*: S1 (MetaSel (Just "_dataVal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))))