disco-0.1.5: Functional programming language for teaching discrete math.
Copyrightdisco team and contributors
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellNone
LanguageHaskell2010

Disco.Typecheck.Graph

Description

A thin layer on top of graphs from the fgl package, which allows dealing with vertices by label instead of by integer Node values.

Synopsis

Documentation

data Graph a Source #

Directed graphs, with vertices labelled by a and unlabelled edges.

Constructors

G (Gr a ()) (Map a Node) (Map Node a) 

Instances

Instances details
Show a => Show (Graph a) Source # 
Instance details

Defined in Disco.Typecheck.Graph

Methods

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

show :: Graph a -> String #

showList :: [Graph a] -> ShowS #

Pretty a => Pretty (Graph a) Source # 
Instance details

Defined in Disco.Typecheck.Graph

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Graph a -> Sem r Doc Source #

mkGraph :: (Show a, Ord a) => Set a -> Set (a, a) -> Graph a Source #

Create a graph with the given set of vertices and directed edges. If any edges refer to vertices that are not in the given vertex set, they will simply be dropped.

nodes :: Graph a -> Set a Source #

Return the set of vertices (nodes) of a graph.

edges :: Ord a => Graph a -> Set (a, a) Source #

Return the set of directed edges of a graph.

map :: Ord b => (a -> b) -> Graph a -> Graph b Source #

Map a function over all the vertices of a graph. Graph is not a Functor instance because of the Ord constraint on b.

delete :: (Show a, Ord a) => a -> Graph a -> Graph a Source #

Delete a vertex.

condensation :: Ord a => Graph a -> Graph (Set a) Source #

The condensation of a graph is the graph of its strongly connected components, i.e. each strongly connected component is compressed to a single node, labelled by the set of vertices in the component. There is an edge from component A to component B in the condensed graph iff there is an edge from any vertex in component A to any vertex in component B in the original graph.

wcc :: Ord a => Graph a -> [Set a] Source #

Get a list of the weakly connected components of a graph, providing the set of vertices in each. Equivalently, return the strongly connected components of the graph when considered as an undirected graph.

wccIDs :: Ord a => Graph a -> [Set (Node, a)] Source #

topsort :: Graph a -> [a] Source #

Do a topological sort on a DAG.

sequenceGraph :: Ord a => Graph (Maybe a) -> Maybe (Graph a) Source #

A miscellaneous utility function to turn a Graph Maybe into a Maybe Graph: the result is Just iff all the vertices in the input graph are.

suc :: (Show a, Ord a) => Graph a -> a -> [a] Source #

Get a list of all the successors of a given node in the graph, i.e. all the nodes reachable from the given node by a directed path. Does not include the given node itself.

pre :: (Show a, Ord a) => Graph a -> a -> [a] Source #

Get a list of all the predecessors of a given node in the graph, i.e. all the nodes from which from the given node is reachable by a directed path. Does not include the given node itself.

cessors :: (Show a, Ord a) => Graph a -> (Map a (Set a), Map a (Set a)) Source #

Given a graph, return two mappings: the first maps each vertex to its set of successors; the second maps each vertex to its set of predecessors. Equivalent to

(M.fromList *** M.fromList) . unzip . map (\a -> ((a, suc g a), (a, pre g a))) . nodes $ g

but much more efficient.