unordered-graphs-0.1.0.1: Graph library using unordered-containers

Copyright(c) Ivan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.Graph.Unordered

Contents

Description

Known limitations:

  • Adding edges might not be the same depending on graph construction (if you add then delete a lot of edges, then the next new edge might be higher than expected).

Synopsis

Graph datatype

data Graph et n nl el Source #

Instances

(Eq (et n), Eq n, Eq nl, Eq el) => Eq (Graph et n nl el) Source # 

Methods

(==) :: Graph et n nl el -> Graph et n nl el -> Bool #

(/=) :: Graph et n nl el -> Graph et n nl el -> Bool #

(ValidGraph et n, Read n, Read nl, Read el) => Read (Graph et n nl el) Source # 

Methods

readsPrec :: Int -> ReadS (Graph et n nl el) #

readList :: ReadS [Graph et n nl el] #

readPrec :: ReadPrec (Graph et n nl el) #

readListPrec :: ReadPrec [Graph et n nl el] #

(EdgeType et, Show n, Show nl, Show el) => Show (Graph et n nl el) Source # 

Methods

showsPrec :: Int -> Graph et n nl el -> ShowS #

show :: Graph et n nl el -> String #

showList :: [Graph et n nl el] -> ShowS #

(NFData n, NFData (et n), NFData nl, NFData el) => NFData (Graph et n nl el) Source # 

Methods

rnf :: Graph et n nl el -> () #

type ValidGraph et n = (Hashable n, Eq n, EdgeType et) Source #

Edge types

newtype Edge Source #

Constructors

Edge 

Fields

Instances

Bounded Edge Source # 
Enum Edge Source # 

Methods

succ :: Edge -> Edge #

pred :: Edge -> Edge #

toEnum :: Int -> Edge #

fromEnum :: Edge -> Int #

enumFrom :: Edge -> [Edge] #

enumFromThen :: Edge -> Edge -> [Edge] #

enumFromTo :: Edge -> Edge -> [Edge] #

enumFromThenTo :: Edge -> Edge -> Edge -> [Edge] #

Eq Edge Source # 

Methods

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

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

Ord Edge Source # 

Methods

compare :: Edge -> Edge -> Ordering #

(<) :: Edge -> Edge -> Bool #

(<=) :: Edge -> Edge -> Bool #

(>) :: Edge -> Edge -> Bool #

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

max :: Edge -> Edge -> Edge #

min :: Edge -> Edge -> Edge #

Read Edge Source # 
Show Edge Source # 

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

NFData Edge Source # 

Methods

rnf :: Edge -> () #

Hashable Edge Source # 

Methods

hashWithSalt :: Int -> Edge -> Int #

hash :: Edge -> Int #

ToContext (n, nl, AdjLookup (at n) el) Source # 

Methods

toContext :: (n, nl, AdjLookup (at n) el) -> Context (CAType (n, nl, AdjLookup (at n) el)) (CNode (n, nl, AdjLookup (at n) el)) (CNLabel (n, nl, AdjLookup (at n) el)) (CELabel (n, nl, AdjLookup (at n) el)) Source #

FromContext (n, nl, AdjLookup (at n) el) Source # 

Methods

fromContext :: Context (CAType (n, nl, AdjLookup (at n) el)) (CNode (n, nl, AdjLookup (at n) el)) (CNLabel (n, nl, AdjLookup (at n) el)) (CELabel (n, nl, AdjLookup (at n) el)) -> (n, nl, AdjLookup (at n) el) Source #

Contextual (n, nl, AdjLookup (at n) el) Source # 

Associated Types

type CNode (n, nl, AdjLookup (at n) el) :: * Source #

type CAType (n, nl, AdjLookup (at n) el) :: * -> * Source #

type CNLabel (n, nl, AdjLookup (at n) el) :: * Source #

type CELabel (n, nl, AdjLookup (at n) el) :: * Source #

type CNode (n, nl, AdjLookup (at n) el) Source # 
type CNode (n, nl, AdjLookup (at n) el) = n
type CAType (n, nl, AdjLookup (at n) el) Source # 
type CAType (n, nl, AdjLookup (at n) el) = at
type CNLabel (n, nl, AdjLookup (at n) el) Source # 
type CNLabel (n, nl, AdjLookup (at n) el) = nl
type CELabel (n, nl, AdjLookup (at n) el) Source # 
type CELabel (n, nl, AdjLookup (at n) el) = el

data DirEdge n Source #

Constructors

DE 

Fields

Instances

Functor DirEdge Source # 

Methods

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

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

EdgeType DirEdge Source #

Note that for loops, the result of otherN will always be a ToNode.

Associated Types

type AdjType (DirEdge :: * -> *) :: * -> * Source #

Methods

mkEdge :: n -> n -> DirEdge n Source #

otherN :: Eq n => n -> DirEdge n -> AdjType DirEdge n Source #

toEdge :: n -> AdjType DirEdge n -> DirEdge n Source #

edgeNodes :: DirEdge n -> [n] Source #

edgeTriple :: (DirEdge n, el) -> (n, n, el) Source #

EdgeMergeable DirEdge Source # 

Methods

applyOpposite :: Fractional el => Proxy (* -> *) DirEdge -> el -> el

Eq n => Eq (DirEdge n) Source # 

Methods

(==) :: DirEdge n -> DirEdge n -> Bool #

(/=) :: DirEdge n -> DirEdge n -> Bool #

Ord n => Ord (DirEdge n) Source # 

Methods

compare :: DirEdge n -> DirEdge n -> Ordering #

(<) :: DirEdge n -> DirEdge n -> Bool #

(<=) :: DirEdge n -> DirEdge n -> Bool #

(>) :: DirEdge n -> DirEdge n -> Bool #

(>=) :: DirEdge n -> DirEdge n -> Bool #

max :: DirEdge n -> DirEdge n -> DirEdge n #

min :: DirEdge n -> DirEdge n -> DirEdge n #

Read n => Read (DirEdge n) Source # 
Show n => Show (DirEdge n) Source # 

Methods

showsPrec :: Int -> DirEdge n -> ShowS #

show :: DirEdge n -> String #

showList :: [DirEdge n] -> ShowS #

Generic (DirEdge n) Source # 

Associated Types

type Rep (DirEdge n) :: * -> * #

Methods

from :: DirEdge n -> Rep (DirEdge n) x #

to :: Rep (DirEdge n) x -> DirEdge n #

NFData n => NFData (DirEdge n) Source # 

Methods

rnf :: DirEdge n -> () #

type AdjType DirEdge Source # 
type Rep (DirEdge n) Source # 
type Rep (DirEdge n) = D1 (MetaData "DirEdge" "Data.Graph.Unordered" "unordered-graphs-0.1.0.1-61V4bCyfvDyCGJtGHI5kzp" False) (C1 (MetaCons "DE" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "fromNode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 n)) (S1 (MetaSel (Just Symbol "toNode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 n))))

newtype UndirEdge n Source #

Constructors

UE 

Fields

Instances

Functor UndirEdge Source # 

Methods

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

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

EdgeType UndirEdge Source # 

Associated Types

type AdjType (UndirEdge :: * -> *) :: * -> * Source #

Methods

mkEdge :: n -> n -> UndirEdge n Source #

otherN :: Eq n => n -> UndirEdge n -> AdjType UndirEdge n Source #

toEdge :: n -> AdjType UndirEdge n -> UndirEdge n Source #

edgeNodes :: UndirEdge n -> [n] Source #

edgeTriple :: (UndirEdge n, el) -> (n, n, el) Source #

EdgeMergeable UndirEdge Source # 

Methods

applyOpposite :: Fractional el => Proxy (* -> *) UndirEdge -> el -> el

Eq n => Eq (UndirEdge n) Source # 

Methods

(==) :: UndirEdge n -> UndirEdge n -> Bool #

(/=) :: UndirEdge n -> UndirEdge n -> Bool #

Ord n => Ord (UndirEdge n) Source # 
Read n => Read (UndirEdge n) Source # 
Show n => Show (UndirEdge n) Source # 
Generic (UndirEdge n) Source # 

Associated Types

type Rep (UndirEdge n) :: * -> * #

Methods

from :: UndirEdge n -> Rep (UndirEdge n) x #

to :: Rep (UndirEdge n) x -> UndirEdge n #

NFData n => NFData (UndirEdge n) Source # 

Methods

rnf :: UndirEdge n -> () #

type AdjType UndirEdge Source # 
type Rep (UndirEdge n) Source # 
type Rep (UndirEdge n) = D1 (MetaData "UndirEdge" "Data.Graph.Unordered" "unordered-graphs-0.1.0.1-61V4bCyfvDyCGJtGHI5kzp" True) (C1 (MetaCons "UE" PrefixI True) (S1 (MetaSel (Just Symbol "ueElem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [n])))

class (Functor et, NodeFrom (AdjType et)) => EdgeType et where Source #

Minimal complete definition

mkEdge, otherN, toEdge, edgeNodes, edgeTriple

Associated Types

type AdjType et :: * -> * Source #

Methods

mkEdge :: n -> n -> et n Source #

otherN :: Eq n => n -> et n -> AdjType et n Source #

Assumes n is one of the end points of this edge.

toEdge :: n -> AdjType et n -> et n Source #

edgeNodes :: et n -> [n] Source #

Returns a list of length 2.

edgeTriple :: (et n, el) -> (n, n, el) Source #

Instances

EdgeType UndirEdge Source # 

Associated Types

type AdjType (UndirEdge :: * -> *) :: * -> * Source #

Methods

mkEdge :: n -> n -> UndirEdge n Source #

otherN :: Eq n => n -> UndirEdge n -> AdjType UndirEdge n Source #

toEdge :: n -> AdjType UndirEdge n -> UndirEdge n Source #

edgeNodes :: UndirEdge n -> [n] Source #

edgeTriple :: (UndirEdge n, el) -> (n, n, el) Source #

EdgeType DirEdge Source #

Note that for loops, the result of otherN will always be a ToNode.

Associated Types

type AdjType (DirEdge :: * -> *) :: * -> * Source #

Methods

mkEdge :: n -> n -> DirEdge n Source #

otherN :: Eq n => n -> DirEdge n -> AdjType DirEdge n Source #

toEdge :: n -> AdjType DirEdge n -> DirEdge n Source #

edgeNodes :: DirEdge n -> [n] Source #

edgeTriple :: (DirEdge n, el) -> (n, n, el) Source #

class NodeFrom at where Source #

Minimal complete definition

getNode

Methods

getNode :: at n -> n Source #

Instances

data DirAdj n Source #

Constructors

ToNode n 
FromNode n 

Instances

NodeFrom DirAdj Source # 

Methods

getNode :: DirAdj n -> n Source #

Eq n => Eq (DirAdj n) Source # 

Methods

(==) :: DirAdj n -> DirAdj n -> Bool #

(/=) :: DirAdj n -> DirAdj n -> Bool #

Ord n => Ord (DirAdj n) Source # 

Methods

compare :: DirAdj n -> DirAdj n -> Ordering #

(<) :: DirAdj n -> DirAdj n -> Bool #

(<=) :: DirAdj n -> DirAdj n -> Bool #

(>) :: DirAdj n -> DirAdj n -> Bool #

(>=) :: DirAdj n -> DirAdj n -> Bool #

max :: DirAdj n -> DirAdj n -> DirAdj n #

min :: DirAdj n -> DirAdj n -> DirAdj n #

Read n => Read (DirAdj n) Source # 
Show n => Show (DirAdj n) Source # 

Methods

showsPrec :: Int -> DirAdj n -> ShowS #

show :: DirAdj n -> String #

showList :: [DirAdj n] -> ShowS #

Generic (DirAdj n) Source # 

Associated Types

type Rep (DirAdj n) :: * -> * #

Methods

from :: DirAdj n -> Rep (DirAdj n) x #

to :: Rep (DirAdj n) x -> DirAdj n #

NFData n => NFData (DirAdj n) Source # 

Methods

rnf :: DirAdj n -> () #

type Rep (DirAdj n) Source # 
type Rep (DirAdj n) = D1 (MetaData "DirAdj" "Data.Graph.Unordered" "unordered-graphs-0.1.0.1-61V4bCyfvDyCGJtGHI5kzp" False) ((:+:) (C1 (MetaCons "ToNode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n))) (C1 (MetaCons "FromNode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n))))

newtype Identity a :: * -> * #

Identity functor and monad. (a non-strict monad)

Since: 4.8.0.0

Constructors

Identity 

Fields

Instances

Monad Identity 

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity 

Methods

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

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

MonadFix Identity 

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity 

Methods

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

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

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

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Generic1 Identity 

Associated Types

type Rep1 (Identity :: * -> *) :: * -> * #

Methods

from1 :: Identity a -> Rep1 Identity a #

to1 :: Rep1 Identity a -> Identity a #

MonadZip Identity 

Methods

mzip :: Identity a -> Identity b -> Identity (a, b) #

mzipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

munzip :: Identity (a, b) -> (Identity a, Identity b) #

NodeFrom Identity Source # 

Methods

getNode :: Identity n -> n Source #

Bounded a => Bounded (Identity a) 
Enum a => Enum (Identity a) 
Eq a => Eq (Identity a) 

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Floating a => Floating (Identity a) 
Fractional a => Fractional (Identity a) 
Integral a => Integral (Identity a) 
Data a => Data (Identity a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity a -> c (Identity a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identity a) #

toConstr :: Identity a -> Constr #

dataTypeOf :: Identity a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Identity a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Identity a)) #

gmapT :: (forall b. Data b => b -> b) -> Identity a -> Identity a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identity a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

Num a => Num (Identity a) 
Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Real a => Real (Identity a) 

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a) 
RealFrac a => RealFrac (Identity a) 

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a) 
IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a) 

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Storable a => Storable (Identity a) 

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a) 
FiniteBits a => FiniteBits (Identity a) 
NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

type Rep1 Identity 
type Rep1 Identity = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Identity a) 
type Rep (Identity a) = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Graph Context

data Context at n nl el Source #

Constructors

Ctxt 

Fields

Instances

(Eq (at n), Eq el, Eq nl, Eq n) => Eq (Context at n nl el) Source # 

Methods

(==) :: Context at n nl el -> Context at n nl el -> Bool #

(/=) :: Context at n nl el -> Context at n nl el -> Bool #

(Read (at n), Read el, Read nl, Read n) => Read (Context at n nl el) Source # 

Methods

readsPrec :: Int -> ReadS (Context at n nl el) #

readList :: ReadS [Context at n nl el] #

readPrec :: ReadPrec (Context at n nl el) #

readListPrec :: ReadPrec [Context at n nl el] #

(Show (at n), Show el, Show nl, Show n) => Show (Context at n nl el) Source # 

Methods

showsPrec :: Int -> Context at n nl el -> ShowS #

show :: Context at n nl el -> String #

showList :: [Context at n nl el] -> ShowS #

Generic (Context at n nl el) Source # 

Associated Types

type Rep (Context at n nl el) :: * -> * #

Methods

from :: Context at n nl el -> Rep (Context at n nl el) x #

to :: Rep (Context at n nl el) x -> Context at n nl el #

(NFData (at n), NFData el, NFData nl, NFData n) => NFData (Context at n nl el) Source # 

Methods

rnf :: Context at n nl el -> () #

ToContext (Context at n nl el) Source # 

Methods

toContext :: Context at n nl el -> Context (CAType (Context at n nl el)) (CNode (Context at n nl el)) (CNLabel (Context at n nl el)) (CELabel (Context at n nl el)) Source #

FromContext (Context at n nl el) Source # 

Methods

fromContext :: Context (CAType (Context at n nl el)) (CNode (Context at n nl el)) (CNLabel (Context at n nl el)) (CELabel (Context at n nl el)) -> Context at n nl el Source #

Contextual (Context at n nl el) Source # 

Associated Types

type CNode (Context at n nl el) :: * Source #

type CAType (Context at n nl el) :: * -> * Source #

type CNLabel (Context at n nl el) :: * Source #

type CELabel (Context at n nl el) :: * Source #

type Rep (Context at n nl el) Source # 
type Rep (Context at n nl el) = D1 (MetaData "Context" "Data.Graph.Unordered" "unordered-graphs-0.1.0.1-61V4bCyfvDyCGJtGHI5kzp" False) (C1 (MetaCons "Ctxt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "cNode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 n)) ((:*:) (S1 (MetaSel (Just Symbol "cLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 nl)) (S1 (MetaSel (Just Symbol "cAdj") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (AdjLookup (at n) el))))))
type CNode (Context at n nl el) Source # 
type CNode (Context at n nl el) = n
type CAType (Context at n nl el) Source # 
type CAType (Context at n nl el) = at
type CNLabel (Context at n nl el) Source # 
type CNLabel (Context at n nl el) = nl
type CELabel (Context at n nl el) Source # 
type CELabel (Context at n nl el) = el

type AdjLookup n el = HashMap Edge (n, el) Source #

class Contextual ctxt Source #

Associated Types

type CNode ctxt :: * Source #

type CAType ctxt :: * -> * Source #

type CNLabel ctxt :: * Source #

type CELabel ctxt :: * Source #

Instances

Contextual (n, nl, [(n, [el])]) Source # 

Associated Types

type CNode (n, nl, [(n, [el])]) :: * Source #

type CAType (n, nl, [(n, [el])]) :: * -> * Source #

type CNLabel (n, nl, [(n, [el])]) :: * Source #

type CELabel (n, nl, [(n, [el])]) :: * Source #

Contextual (n, nl, AdjLookup (at n) el) Source # 

Associated Types

type CNode (n, nl, AdjLookup (at n) el) :: * Source #

type CAType (n, nl, AdjLookup (at n) el) :: * -> * Source #

type CNLabel (n, nl, AdjLookup (at n) el) :: * Source #

type CELabel (n, nl, AdjLookup (at n) el) :: * Source #

Contextual (Context at n nl el) Source # 

Associated Types

type CNode (Context at n nl el) :: * Source #

type CAType (Context at n nl el) :: * -> * Source #

type CNLabel (Context at n nl el) :: * Source #

type CELabel (Context at n nl el) :: * Source #

type ValidContext et n nl el ctxt = (Contextual ctxt, n ~ CNode ctxt, AdjType et ~ CAType ctxt, nl ~ CNLabel ctxt, el ~ CELabel ctxt) Source #

class Contextual ctxt => FromContext ctxt where Source #

Minimal complete definition

fromContext

Methods

fromContext :: Context (CAType ctxt) (CNode ctxt) (CNLabel ctxt) (CELabel ctxt) -> ctxt Source #

Instances

Ord n => FromContext (n, nl, [(n, [el])]) Source # 

Methods

fromContext :: Context (CAType (n, nl, [(n, [el])])) (CNode (n, nl, [(n, [el])])) (CNLabel (n, nl, [(n, [el])])) (CELabel (n, nl, [(n, [el])])) -> (n, nl, [(n, [el])]) Source #

FromContext (n, nl, AdjLookup (at n) el) Source # 

Methods

fromContext :: Context (CAType (n, nl, AdjLookup (at n) el)) (CNode (n, nl, AdjLookup (at n) el)) (CNLabel (n, nl, AdjLookup (at n) el)) (CELabel (n, nl, AdjLookup (at n) el)) -> (n, nl, AdjLookup (at n) el) Source #

FromContext (Context at n nl el) Source # 

Methods

fromContext :: Context (CAType (Context at n nl el)) (CNode (Context at n nl el)) (CNLabel (Context at n nl el)) (CELabel (Context at n nl el)) -> Context at n nl el Source #

class Contextual ctxt => ToContext ctxt where Source #

Minimal complete definition

toContext

Methods

toContext :: ctxt -> Context (CAType ctxt) (CNode ctxt) (CNLabel ctxt) (CELabel ctxt) Source #

Instances

ToContext (n, nl, AdjLookup (at n) el) Source # 

Methods

toContext :: (n, nl, AdjLookup (at n) el) -> Context (CAType (n, nl, AdjLookup (at n) el)) (CNode (n, nl, AdjLookup (at n) el)) (CNLabel (n, nl, AdjLookup (at n) el)) (CELabel (n, nl, AdjLookup (at n) el)) Source #

ToContext (Context at n nl el) Source # 

Methods

toContext :: Context at n nl el -> Context (CAType (Context at n nl el)) (CNode (Context at n nl el)) (CNLabel (Context at n nl el)) (CELabel (Context at n nl el)) Source #

Graph functions

Graph Information

isEmpty :: Graph et n nl el -> Bool Source #

Node information

order :: Graph et n nl el -> Int Source #

Number of nodes

hasNode :: ValidGraph et n => Graph et n nl el -> n -> Bool Source #

ninfo :: ValidGraph et n => Graph et n nl el -> n -> Maybe ([Edge], nl) Source #

nodes :: Graph et n nl el -> [n] Source #

nodeDetails :: Graph et n nl el -> [(n, ([Edge], nl))] Source #

lnodes :: Graph et n nl el -> [(n, nl)] Source #

nlab :: ValidGraph et n => Graph et n nl el -> n -> Maybe nl Source #

neighbours :: ValidGraph et n => Graph et n nl el -> n -> [n] Source #

Edge information

size :: Graph et n nl el -> Int Source #

Number of edges

hasEdge :: Graph et n nl el -> Edge -> Bool Source #

einfo :: Graph et n nl el -> Edge -> Maybe (et n, el) Source #

edges :: Graph et n nl el -> [Edge] Source #

edgeDetails :: Graph et n nl el -> [(Edge, (et n, el))] Source #

ledges :: Graph et n nl el -> [(Edge, el)] Source #

elab :: Graph et n nl el -> Edge -> Maybe el Source #

edgePairs :: EdgeType et => Graph et n nl el -> [(n, n)] Source #

ledgePairs :: EdgeType et => Graph et n nl el -> [(n, n, el)] Source #

Graph construction

empty :: Graph et n nl el Source #

mkGraph :: ValidGraph et n => [(n, nl)] -> [(n, n, el)] -> Graph et n nl el Source #

Assumes all nodes are in the node list.

buildGr :: ValidGraph et n => [Context (AdjType et) n nl el] -> Graph et n nl el Source #

Assumes the Contexts describe a graph in total, with the outermost one first (i.e. buildGr (c:cs) == c merge buildGr cs).

insNode :: ValidGraph et n => n -> nl -> Graph et n nl el -> Graph et n nl el Source #

insEdge :: ValidGraph et n => (n, n, el) -> Graph et n nl el -> (Edge, Graph et n nl el) Source #

Merging

type Mergeable et n nl el ctxt = (ValidGraph et n, ToContext ctxt, ValidContext et n nl el ctxt) Source #

merge :: ValidGraph et n => Context (AdjType et) n nl el -> Graph et n nl el -> Graph et n nl el Source #

mergeAs :: Mergeable et n nl el ctxt => ctxt -> Graph et n nl el -> Graph et n nl el Source #

Graph deconstruction

delNode :: ValidGraph et n => n -> Graph et n nl el -> Graph et n nl el Source #

delEdge :: ValidGraph et n => Edge -> Graph et n nl el -> Graph et n nl el Source #

delEdgeLabel :: (ValidGraph et n, Eq el) => (n, n, el) -> Graph et n nl el -> Graph et n nl el Source #

delEdgesBetween :: ValidGraph et n => n -> n -> Graph et n nl el -> Graph et n nl el Source #

Matching

type Matchable et n nl el ctxt = (ValidGraph et n, FromContext ctxt, ValidContext et n nl el ctxt) Source #

match :: ValidGraph et n => n -> Graph et n nl el -> Maybe (Context (AdjType et) n nl el, Graph et n nl el) Source #

Note that for any loops, the resultant edge will only appear once in the output cAdj field.

matchAs :: Matchable et n nl el ctxt => n -> Graph et n nl el -> Maybe (ctxt, Graph et n nl el) Source #

matchAny :: ValidGraph et n => Graph et n nl el -> Maybe (Context (AdjType et) n nl el, Graph et n nl el) Source #

matchAnyAs :: Matchable et n nl el ctxt => Graph et n nl el -> Maybe (ctxt, Graph et n nl el) Source #

Manipulation

nmap :: (nl -> nl') -> Graph et n nl el -> Graph et n nl' el Source #

nmapFor :: ValidGraph et n => (nl -> nl) -> Graph et n nl el -> n -> Graph et n nl el Source #

emap :: (el -> el') -> Graph et n nl el -> Graph et n nl el' Source #

emapFor :: (el -> el) -> Graph et n nl el -> Edge -> Graph et n nl el Source #