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

Data.Geometry.PlanarSubdivision.TreeRep

Description

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

Synopsis

Documentation

data PlanarSD v e f r Source #

Specify the planar subdivison as a tree of components

Constructors

PlanarSD 

Fields

Instances

Instances details
Functor (PlanarSD v e f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.TreeRep

Methods

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

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

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

Defined in Data.Geometry.PlanarSubdivision.TreeRep

Methods

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

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

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

Defined in Data.Geometry.PlanarSubdivision.TreeRep

Methods

showsPrec :: Int -> PlanarSD v e f r -> ShowS #

show :: PlanarSD v e f r -> String #

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

Generic (PlanarSD v e f r) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.TreeRep

Associated Types

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

Methods

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

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

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

Defined in Data.Geometry.PlanarSubdivision.TreeRep

Methods

toJSON :: PlanarSD v e f r -> Value #

toEncoding :: PlanarSD v e f r -> Encoding #

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

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

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

Defined in Data.Geometry.PlanarSubdivision.TreeRep

Methods

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

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

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

Defined in Data.Geometry.PlanarSubdivision.TreeRep

type Rep (PlanarSD v e f r)

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.14-BBhGh1sNn85H5mfsjBn14s" '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))))

myTreeRep :: PlanarSD Int () String (RealNumber 3) Source #

This represents the following Planar subdivision. Note that the graph is undirected, the arrows are just to indicate what the Positive direction of the darts is.