ghc-lib-parser-8.10.1.20200916: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

Digraph

Synopsis

Documentation

data Graph node Source #

Instances
Outputable node => Outputable (Graph node) Source # 
Instance details

Defined in Digraph

Methods

ppr :: Graph node -> SDoc Source #

pprPrec :: Rational -> Graph node -> SDoc Source #

graphFromEdgedVerticesOrd :: Ord key => [Node key payload] -> Graph (Node key payload) Source #

graphFromEdgedVerticesUniq :: Uniquable key => [Node key payload] -> Graph (Node key payload) Source #

data SCC vertex #

Strongly connected component.

Constructors

AcyclicSCC vertex

A single vertex that is not in any cycle.

CyclicSCC [vertex]

A maximal set of mutually reachable vertices.

Instances
Functor SCC

Since: containers-0.5.4

Instance details

Defined in Data.Graph

Methods

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

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

Foldable SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

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

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

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

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

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

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

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

toList :: SCC a -> [a] #

null :: SCC a -> Bool #

length :: SCC a -> Int #

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

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

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

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

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

Traversable SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

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

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

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

Eq1 SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

liftEq :: (a -> b -> Bool) -> SCC a -> SCC b -> Bool #

Read1 SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (SCC a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [SCC a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (SCC a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [SCC a] #

Show1 SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SCC a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [SCC a] -> ShowS #

Eq vertex => Eq (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

(==) :: SCC vertex -> SCC vertex -> Bool #

(/=) :: SCC vertex -> SCC vertex -> Bool #

Data vertex => Data (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SCC vertex -> c (SCC vertex) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SCC vertex) #

toConstr :: SCC vertex -> Constr #

dataTypeOf :: SCC vertex -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SCC vertex)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SCC vertex)) #

gmapT :: (forall b. Data b => b -> b) -> SCC vertex -> SCC vertex #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r #

gmapQ :: (forall d. Data d => d -> u) -> SCC vertex -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SCC vertex -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) #

Read vertex => Read (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

readsPrec :: Int -> ReadS (SCC vertex) #

readList :: ReadS [SCC vertex] #

readPrec :: ReadPrec (SCC vertex) #

readListPrec :: ReadPrec [SCC vertex] #

Show vertex => Show (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

showsPrec :: Int -> SCC vertex -> ShowS #

show :: SCC vertex -> String #

showList :: [SCC vertex] -> ShowS #

Generic (SCC vertex) 
Instance details

Defined in Data.Graph

Associated Types

type Rep (SCC vertex) :: Type -> Type #

Methods

from :: SCC vertex -> Rep (SCC vertex) x #

to :: Rep (SCC vertex) x -> SCC vertex #

NFData a => NFData (SCC a) 
Instance details

Defined in Data.Graph

Methods

rnf :: SCC a -> () #

Outputable a => Outputable (SCC a) Source # 
Instance details

Defined in Outputable

Methods

ppr :: SCC a -> SDoc Source #

pprPrec :: Rational -> SCC a -> SDoc Source #

Generic1 SCC 
Instance details

Defined in Data.Graph

Associated Types

type Rep1 SCC :: k -> Type #

Methods

from1 :: SCC a -> Rep1 SCC a #

to1 :: Rep1 SCC a -> SCC a #

type Rep (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

type Rep (SCC vertex) = D1 (MetaData "SCC" "Data.Graph" "containers-0.6.0.1" False) (C1 (MetaCons "AcyclicSCC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 vertex)) :+: C1 (MetaCons "CyclicSCC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [vertex])))
type Rep1 SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

data Node key payload Source #

Representation for nodes of the Graph.

  • The payload is user data, just carried around in this module
  • The key is the node identifier. Key has an Ord instance for performance reasons.
  • The [key] are the dependencies of the node; it's ok to have extra keys in the dependencies that are not the key of any Node in the graph

Constructors

DigraphNode 

Fields

Instances
(Outputable a, Outputable b) => Outputable (Node a b) Source # 
Instance details

Defined in Digraph

Methods

ppr :: Node a b -> SDoc Source #

pprPrec :: Rational -> Node a b -> SDoc Source #

flattenSCC :: SCC vertex -> [vertex] #

The vertices of a strongly connected component.

flattenSCCs :: [SCC a] -> [a] #

The vertices of a list of strongly connected components.

stronglyConnCompG :: Graph node -> [SCC node] Source #

topologicalSortG :: Graph node -> [node] Source #

verticesG :: Graph node -> [node] Source #

edgesG :: Graph node -> [Edge node] Source #

hasVertexG :: Graph node -> node -> Bool Source #

reachableG :: Graph node -> node -> [node] Source #

reachablesG :: Graph node -> [node] -> [node] Source #

Given a list of roots return all reachable nodes.

transposeG :: Graph node -> Graph node Source #

emptyG :: Graph node -> Bool Source #

findCycle :: forall payload key. Ord key => [Node key payload] -> Maybe [payload] Source #

Find a reasonably short cycle a->b->c->a, in a strongly connected component. The input nodes are presumed to be a SCC, so you can start anywhere.

stronglyConnCompFromEdgedVerticesOrd :: Ord key => [Node key payload] -> [SCC payload] Source #

stronglyConnCompFromEdgedVerticesOrdR :: Ord key => [Node key payload] -> [SCC (Node key payload)] Source #

stronglyConnCompFromEdgedVerticesUniq :: Uniquable key => [Node key payload] -> [SCC payload] Source #

stronglyConnCompFromEdgedVerticesUniqR :: Uniquable key => [Node key payload] -> [SCC (Node key payload)] Source #

data EdgeType Source #

Edge direction based on DFS Classification

Constructors

Forward 
Cross 
Backward

Loop back towards the root node. Eg backjumps in loops

SelfLoop

v -> v

Instances
Eq EdgeType Source # 
Instance details

Defined in Digraph

Ord EdgeType Source # 
Instance details

Defined in Digraph

Outputable EdgeType Source # 
Instance details

Defined in Digraph

classifyEdges :: forall key. Uniquable key => key -> (key -> [key]) -> [(key, key)] -> [((key, key), EdgeType)] Source #

Given a start vertex, a way to get successors from a node and a list of (directed) edges classify the types of edges.