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

Data.PlaneGraph.AdjRep

Description

Data types that help encodedecode a planegraph as a JSONYAML file.

Synopsis

Documentation

data Gr v f #

Data type representing the graph in its JSON/Yaml format

Constructors

Gr 

Fields

Instances

Instances details
Bifunctor Gr 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

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

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

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

(Eq v, Eq f) => Eq (Gr v f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

(==) :: Gr v f -> Gr v f -> Bool #

(/=) :: Gr v f -> Gr v f -> Bool #

(Show v, Show f) => Show (Gr v f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

showsPrec :: Int -> Gr v f -> ShowS #

show :: Gr v f -> String #

showList :: [Gr v f] -> ShowS #

Generic (Gr v f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Associated Types

type Rep (Gr v f) :: Type -> Type #

Methods

from :: Gr v f -> Rep (Gr v f) x #

to :: Rep (Gr v f) x -> Gr v f #

(ToJSON v, ToJSON f) => ToJSON (Gr v f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

toJSON :: Gr v f -> Value #

toEncoding :: Gr v f -> Encoding #

toJSONList :: [Gr v f] -> Value #

toEncodingList :: [Gr v f] -> Encoding #

(FromJSON v, FromJSON f) => FromJSON (Gr v f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

parseJSON :: Value -> Parser (Gr v f) #

parseJSONList :: Value -> Parser [Gr v f] #

type Rep (Gr v f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

type Rep (Gr v f) = D1 ('MetaData "Gr" "Data.PlanarGraph.AdjRep" "hgeometry-combinatorial-0.13-FqkqJCsl9I37c4Aln2AxaY" 'False) (C1 ('MetaCons "Gr" 'PrefixI 'True) (S1 ('MetaSel ('Just "adjacencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [v]) :*: S1 ('MetaSel ('Just "faces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [f])))

data Vtx v e r Source #

A vertex, represented by an id, location, its adjacencies, and its data.

Constructors

Vtx 

Fields

  • id :: Int
     
  • loc :: Point 2 r
     
  • adj :: [(Int, e)]

    adjacent vertices + data on the edge. Adjacencies are given in arbitrary order

  • vData :: v
     

Instances

Instances details
Functor (Vtx v e) Source # 
Instance details

Defined in Data.PlaneGraph.AdjRep

Methods

fmap :: (a -> b) -> Vtx v e a -> Vtx v e b #

(<$) :: a -> Vtx v e b -> Vtx v e a #

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

Defined in Data.PlaneGraph.AdjRep

Methods

(==) :: Vtx v e r -> Vtx v e r -> Bool #

(/=) :: Vtx v e r -> Vtx v e r -> Bool #

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

Defined in Data.PlaneGraph.AdjRep

Methods

showsPrec :: Int -> Vtx v e r -> ShowS #

show :: Vtx v e r -> String #

showList :: [Vtx v e r] -> ShowS #

Generic (Vtx v e r) Source # 
Instance details

Defined in Data.PlaneGraph.AdjRep

Associated Types

type Rep (Vtx v e r) :: Type -> Type #

Methods

from :: Vtx v e r -> Rep (Vtx v e r) x #

to :: Rep (Vtx v e r) x -> Vtx v e r #

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

Defined in Data.PlaneGraph.AdjRep

Methods

toJSON :: Vtx v e r -> Value #

toEncoding :: Vtx v e r -> Encoding #

toJSONList :: [Vtx v e r] -> Value #

toEncodingList :: [Vtx v e r] -> Encoding #

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

Defined in Data.PlaneGraph.AdjRep

Methods

parseJSON :: Value -> Parser (Vtx v e r) #

parseJSONList :: Value -> Parser [Vtx v e r] #

type Rep (Vtx v e r) Source # 
Instance details

Defined in Data.PlaneGraph.AdjRep

type Rep (Vtx v e r) = D1 ('MetaData "Vtx" "Data.PlaneGraph.AdjRep" "hgeometry-0.13-8qLvB9JVk1yDS01KUXpxiU" 'False) (C1 ('MetaCons "Vtx" 'PrefixI 'True) ((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point 2 r))) :*: (S1 ('MetaSel ('Just "adj") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, e)]) :*: S1 ('MetaSel ('Just "vData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v))))

data Face f #

Faces

Constructors

Face 

Fields

Instances

Instances details
Functor Face 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

fmap :: (a -> b) -> Face a -> Face b #

(<$) :: a -> Face b -> Face a #

Eq f => Eq (Face f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

(==) :: Face f -> Face f -> Bool #

(/=) :: Face f -> Face f -> Bool #

Show f => Show (Face f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Methods

showsPrec :: Int -> Face f -> ShowS #

show :: Face f -> String #

showList :: [Face f] -> ShowS #

Generic (Face f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

Associated Types

type Rep (Face f) :: Type -> Type #

Methods

from :: Face f -> Rep (Face f) x #

to :: Rep (Face f) x -> Face f #

ToJSON f => ToJSON (Face f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

FromJSON f => FromJSON (Face f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

type Rep (Face f) 
Instance details

Defined in Data.PlanarGraph.AdjRep

type Rep (Face f) = D1 ('MetaData "Face" "Data.PlanarGraph.AdjRep" "hgeometry-combinatorial-0.13-FqkqJCsl9I37c4Aln2AxaY" 'False) (C1 ('MetaCons "Face" 'PrefixI 'True) (S1 ('MetaSel ('Just "incidentEdge") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Just "fData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))