Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Graph node
- graphFromEdgedVerticesOrd :: Ord key => [Node key payload] -> Graph (Node key payload)
- graphFromEdgedVerticesUniq :: Uniquable key => [Node key payload] -> Graph (Node key payload)
- data SCC vertex
- = AcyclicSCC vertex
- | CyclicSCC [vertex]
- data Node key payload = DigraphNode {
- node_payload :: payload
- node_key :: key
- node_dependencies :: [key]
- flattenSCC :: SCC vertex -> [vertex]
- flattenSCCs :: [SCC a] -> [a]
- stronglyConnCompG :: Graph node -> [SCC node]
- topologicalSortG :: Graph node -> [node]
- verticesG :: Graph node -> [node]
- edgesG :: Graph node -> [Edge node]
- hasVertexG :: Graph node -> node -> Bool
- reachableG :: Graph node -> node -> [node]
- reachablesG :: Graph node -> [node] -> [node]
- transposeG :: Graph node -> Graph node
- emptyG :: Graph node -> Bool
- findCycle :: forall payload key. Ord key => [Node key payload] -> Maybe [payload]
- stronglyConnCompFromEdgedVerticesOrd :: Ord key => [Node key payload] -> [SCC payload]
- stronglyConnCompFromEdgedVerticesOrdR :: Ord key => [Node key payload] -> [SCC (Node key payload)]
- stronglyConnCompFromEdgedVerticesUniq :: Uniquable key => [Node key payload] -> [SCC payload]
- stronglyConnCompFromEdgedVerticesUniqR :: Uniquable key => [Node key payload] -> [SCC (Node key payload)]
Documentation
graphFromEdgedVerticesUniq :: Uniquable key => [Node key payload] -> Graph (Node key payload) Source #
Strongly connected component.
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 |
Foldable SCC | Since: containers-0.5.9 |
Defined in Data.Graph fold :: Monoid m => SCC m -> m Source # foldMap :: Monoid m => (a -> m) -> SCC a -> m Source # foldr :: (a -> b -> b) -> b -> SCC a -> b Source # foldr' :: (a -> b -> b) -> b -> SCC a -> b Source # foldl :: (b -> a -> b) -> b -> SCC a -> b Source # foldl' :: (b -> a -> b) -> b -> SCC a -> b Source # foldr1 :: (a -> a -> a) -> SCC a -> a Source # foldl1 :: (a -> a -> a) -> SCC a -> a Source # toList :: SCC a -> [a] Source # null :: SCC a -> Bool Source # length :: SCC a -> Int Source # elem :: Eq a => a -> SCC a -> Bool Source # maximum :: Ord a => SCC a -> a Source # minimum :: Ord a => SCC a -> a Source # | |
Traversable SCC | Since: containers-0.5.9 |
Eq1 SCC | Since: containers-0.5.9 |
Read1 SCC | Since: containers-0.5.9 |
Defined in Data.Graph | |
Show1 SCC | Since: containers-0.5.9 |
Eq vertex => Eq (SCC vertex) | Since: containers-0.5.9 |
Data vertex => Data (SCC vertex) | Since: containers-0.5.9 |
Defined in Data.Graph gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SCC vertex -> c (SCC vertex) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SCC vertex) Source # toConstr :: SCC vertex -> Constr Source # dataTypeOf :: SCC vertex -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SCC vertex)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SCC vertex)) Source # gmapT :: (forall b. Data b => b -> b) -> SCC vertex -> SCC vertex Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SCC vertex -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SCC vertex -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source # | |
Read vertex => Read (SCC vertex) | Since: containers-0.5.9 |
Show vertex => Show (SCC vertex) | Since: containers-0.5.9 |
Generic (SCC vertex) | |
NFData a => NFData (SCC a) | |
Defined in Data.Graph | |
Outputable a => Outputable (SCC a) # | |
Generic1 SCC | |
type Rep (SCC vertex) | Since: containers-0.5.9 |
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 |
Defined in Data.Graph type Rep1 SCC = D1 (MetaData "SCC" "Data.Graph" "containers-0.6.0.1" False) (C1 (MetaCons "AcyclicSCC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1) :+: C1 (MetaCons "CyclicSCC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 []))) |
data Node key payload Source #
DigraphNode | |
|
flattenSCC :: SCC vertex -> [vertex] Source #
The vertices of a strongly connected component.
flattenSCCs :: [SCC a] -> [a] Source #
The vertices of a list of strongly connected components.
stronglyConnCompG :: Graph node -> [SCC node] Source #
topologicalSortG :: Graph node -> [node] Source #
hasVertexG :: Graph node -> node -> Bool Source #
reachableG :: Graph node -> node -> [node] Source #
reachablesG :: Graph node -> [node] -> [node] Source #
transposeG :: Graph node -> Graph node 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.
stronglyConnCompFromEdgedVerticesOrdR :: Ord key => [Node key payload] -> [SCC (Node key payload)] Source #