containers-0.7: Assorted concrete container types
Copyright(c) The University of Glasgow 2002
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Graph

Description

Finite Graphs

The Graph type is an adjacency list representation of a finite, directed graph with vertices of type Int.

The SCC type represents a strongly-connected component of a graph.

Implementation

The implementation is based on

Synopsis

Graphs

type Graph = Array Vertex [Vertex] Source #

Adjacency list representation of a graph, mapping each vertex to its list of successors.

type Bounds = (Vertex, Vertex) Source #

The bounds of an Array.

type Edge = (Vertex, Vertex) Source #

An edge from the first vertex to the second.

type Vertex = Int Source #

Abstract representation of vertices.

type Table a = Array Vertex a Source #

Table indexed by a contiguous set of vertices.

Note: This is included for backwards compatibility.

Graph Construction

graphFromEdges :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex) Source #

\(O((V+E) \log V)\). Build a graph from a list of nodes uniquely identified by keys, with a list of keys of nodes this node should have edges to.

This function takes an adjacency list representing a graph with vertices of type key labeled by values of type node and produces a Graph-based representation of that list. The Graph result represents the shape of the graph, and the functions describe a) how to retrieve the label and adjacent vertices of a given vertex, and b) how to retrieve a vertex given a key.

(graph, nodeFromVertex, vertexFromKey) = graphFromEdges edgeList
  • graph :: Graph is the raw, array based adjacency list for the graph.
  • nodeFromVertex :: Vertex -> (node, key, [key]) returns the node associated with the given 0-based Int vertex; see warning below. This runs in \(O(1)\) time.
  • vertexFromKey :: key -> Maybe Vertex returns the Int vertex for the key if it exists in the graph, Nothing otherwise. This runs in \(O(\log V)\) time.

To safely use this API you must either extract the list of vertices directly from the graph or first call vertexFromKey k to check if a vertex corresponds to the key k. Once it is known that a vertex exists you can use nodeFromVertex to access the labelled node and adjacent vertices. See below for examples.

Note: The out-list may contain keys that don't correspond to nodes of the graph; they are ignored.

Warning: The nodeFromVertex function will cause a runtime exception if the given Vertex does not exist.

Examples

Expand

An empty graph.

(graph, nodeFromVertex, vertexFromKey) = graphFromEdges []
graph = array (0,-1) []

A graph where the out-list references unspecified nodes ('c'), these are ignored.

(graph, _, _) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c'])]
array (0,1) [(0,[1]),(1,[])]

A graph with 3 vertices: ("a") -> ("b") -> ("c")

(graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
graph == array (0,2) [(0,[1]),(1,[2]),(2,[])]
nodeFromVertex 0 == ("a",'a',"b")
vertexFromKey 'a' == Just 0

Get the label for a given key.

let getNodePart (n, _, _) = n
(graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
getNodePart . nodeFromVertex <$> vertexFromKey 'a' == Just "A"

graphFromEdges' :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key])) Source #

\(O((V+E) \log V)\). Identical to graphFromEdges, except that the return value does not include the function which maps keys to vertices. This version of graphFromEdges is for backwards compatibility.

buildG :: Bounds -> [Edge] -> Graph Source #

\(O(V+E)\). Build a graph from a list of edges.

Warning: This function will cause a runtime exception if a vertex in the edge list is not within the given Bounds.

Examples

Expand
buildG (0,-1) [] == array (0,-1) []
buildG (0,2) [(0,1), (1,2)] == array (0,1) [(0,[1]),(1,[2])]
buildG (0,2) [(0,1), (0,2), (1,2)] == array (0,2) [(0,[2,1]),(1,[2]),(2,[])]

Graph Properties

vertices :: Graph -> [Vertex] Source #

\(O(V)\). Returns the list of vertices in the graph.

Examples

Expand
vertices (buildG (0,-1) []) == []
vertices (buildG (0,2) [(0,1),(1,2)]) == [0,1,2]

edges :: Graph -> [Edge] Source #

\(O(V+E)\). Returns the list of edges in the graph.

Examples

Expand
edges (buildG (0,-1) []) == []
edges (buildG (0,2) [(0,1),(1,2)]) == [(0,1),(1,2)]

outdegree :: Graph -> Array Vertex Int Source #

\(O(V+E)\). A table of the count of edges from each node.

Examples

Expand
outdegree (buildG (0,-1) []) == array (0,-1) []
outdegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,1),(1,1),(2,0)]

indegree :: Graph -> Array Vertex Int Source #

\(O(V+E)\). A table of the count of edges into each node.

Examples

Expand
indegree (buildG (0,-1) []) == array (0,-1) []
indegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,0),(1,1),(2,1)]

Graph Transformations

transposeG :: Graph -> Graph Source #

\(O(V+E)\). The graph obtained by reversing all edges.

Examples

Expand
transposeG (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,[]),(1,[0]),(2,[1])]

Graph Algorithms

dfs :: Graph -> [Vertex] -> [Tree Vertex] Source #

\(O(V+E)\). A spanning forest of the part of the graph reachable from the listed vertices, obtained from a depth-first search of the graph starting at each of the listed vertices in order.

dff :: Graph -> [Tree Vertex] Source #

\(O(V+E)\). A spanning forest of the graph, obtained from a depth-first search of the graph starting from each vertex in an unspecified order.

topSort :: Graph -> [Vertex] Source #

\(O(V+E)\). A topological sort of the graph. The order is partially specified by the condition that a vertex i precedes j whenever j is reachable from i but not vice versa.

Note: A topological sort exists only when there are no cycles in the graph. If the graph has cycles, the output of this function will not be a topological sort. In such a case consider using scc.

reverseTopSort :: Graph -> [Vertex] Source #

\(O(V+E)\). Reverse ordering of topSort.

See note in topSort.

Since: containers-0.6.4

components :: Graph -> [Tree Vertex] Source #

\(O(V+E)\). The connected components of a graph. Two vertices are connected if there is a path between them, traversing edges in either direction.

scc :: Graph -> [Tree Vertex] Source #

\(O(V+E)\). The strongly connected components of a graph, in reverse topological order.

Examples

Expand
scc (buildG (0,3) [(3,1),(1,2),(2,0),(0,1)])
  == [Node {rootLabel = 0, subForest = [Node {rootLabel = 1, subForest = [Node {rootLabel = 2, subForest = []}]}]}
     ,Node {rootLabel = 3, subForest = []}]

bcc :: Graph -> [Tree [Vertex]] Source #

\(O(V+E)\). The biconnected components of a graph. An undirected graph is biconnected if the deletion of any vertex leaves it connected.

The input graph is expected to be undirected, i.e. for every edge in the graph the reverse edge is also in the graph. If the graph is not undirected the output is arbitrary.

reachable :: Graph -> Vertex -> [Vertex] Source #

\(O(V+E)\). Returns the list of vertices reachable from a given vertex.

Examples

Expand
reachable (buildG (0,0) []) 0 == [0]
reachable (buildG (0,2) [(0,1), (1,2)]) 0 == [0,1,2]

path :: Graph -> Vertex -> Vertex -> Bool Source #

\(O(V+E)\). Returns True if the second vertex reachable from the first.

Examples

Expand
path (buildG (0,0) []) 0 0 == True
path (buildG (0,2) [(0,1), (1,2)]) 0 2 == True
path (buildG (0,2) [(0,1), (1,2)]) 2 0 == False

Strongly Connected Components

data SCC vertex Source #

Strongly connected component.

Constructors

AcyclicSCC vertex

A single vertex that is not in any cycle.

NECyclicSCC !(NonEmpty vertex)

A maximal set of mutually reachable vertices.

Since: containers-0.7.0

Bundled Patterns

pattern CyclicSCC :: [vertex] -> SCC vertex

Partial pattern synonym for backward compatibility with containers < 0.7.

Instances

Instances details
Foldable1 SCC Source #

Since: containers-0.7.0

Instance details

Defined in Data.Graph

Methods

fold1 :: Semigroup m => SCC m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> SCC a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> SCC a -> m Source #

toNonEmpty :: SCC a -> NonEmpty a Source #

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

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

head :: SCC a -> a Source #

last :: SCC a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> SCC a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> SCC a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> SCC a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> SCC a -> b Source #

Eq1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

Read1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

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

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

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

Show1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

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

Functor SCC Source #

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 Source #

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 #

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 Source #

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) #

Generic1 SCC Source # 
Instance details

Defined in Data.Graph

Associated Types

type Rep1 SCC

Since: containers-0.5.9

Instance details

Defined in Data.Graph

type Rep1 SCC = D1 ('MetaData "SCC" "Data.Graph" "containers-0.7-inplace" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "NECyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec1 NonEmpty)))

Methods

from1 :: SCC a -> Rep1 SCC a #

to1 :: Rep1 SCC a -> SCC a #

Lift vertex => Lift (SCC vertex :: Type) Source #

Since: containers-0.6.6

Instance details

Defined in Data.Graph

Methods

lift :: Quote m => SCC vertex -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => SCC vertex -> Code m (SCC vertex) Source #

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

Defined in Data.Graph

Methods

rnf :: SCC a -> () Source #

Data vertex => Data (SCC vertex) Source #

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 :: forall r r'. (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) #

Generic (SCC vertex) Source # 
Instance details

Defined in Data.Graph

Associated Types

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.7-inplace" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 vertex)) :+: C1 ('MetaCons "NECyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty vertex))))

Methods

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

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

Read vertex => Read (SCC vertex) Source #

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) Source #

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 #

Eq vertex => Eq (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

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

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

type Rep1 SCC Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

type Rep1 SCC = D1 ('MetaData "SCC" "Data.Graph" "containers-0.7-inplace" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "NECyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec1 NonEmpty)))
type Rep (SCC vertex) Source #

Since: containers-0.5.9

Instance details

Defined in Data.Graph

type Rep (SCC vertex) = D1 ('MetaData "SCC" "Data.Graph" "containers-0.7-inplace" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 vertex)) :+: C1 ('MetaCons "NECyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty vertex))))

Construction

stronglyConnComp Source #

Arguments

:: Ord key 
=> [(node, key, [key])]

The graph: a list of nodes uniquely identified by keys, with a list of keys of nodes this node has edges to. The out-list may contain keys that don't correspond to nodes of the graph; such edges are ignored.

-> [SCC node] 

\(O((V+E) \log V)\). The strongly connected components of a directed graph, reverse topologically sorted.

Examples

Expand
stronglyConnComp [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
  == [CyclicSCC ["d"],CyclicSCC ["b","c"],AcyclicSCC "a"]

stronglyConnCompR Source #

Arguments

:: Ord key 
=> [(node, key, [key])]

The graph: a list of nodes uniquely identified by keys, with a list of keys of nodes this node has edges to. The out-list may contain keys that don't correspond to nodes of the graph; such edges are ignored.

-> [SCC (node, key, [key])]

Reverse topologically sorted

\(O((V+E) \log V)\). The strongly connected components of a directed graph, reverse topologically sorted. The function is the same as stronglyConnComp, except that all the information about each node retained. This interface is used when you expect to apply SCC to (some of) the result of SCC, so you don't want to lose the dependency information.

Examples

Expand
stronglyConnCompR [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
 == [CyclicSCC [("d",3,[3])],CyclicSCC [("b",1,[2,3]),("c",2,[1])],AcyclicSCC ("a",0,[1])]

Conversion

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.

Trees

data Tree a Source #

Non-empty, possibly infinite, multi-way trees; also known as rose trees.

Constructors

Node a [Tree a] 

Instances

Instances details
MonadZip Tree Source #

Since: containers-0.5.10.1

Instance details

Defined in Data.Tree

Methods

mzip :: Tree a -> Tree b -> Tree (a, b) Source #

mzipWith :: (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

munzip :: Tree (a, b) -> (Tree a, Tree b) Source #

Foldable1 Tree Source #

Folds in preorder

Since: containers-0.6.7

Instance details

Defined in Data.Tree

Methods

fold1 :: Semigroup m => Tree m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Tree a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Tree a -> m Source #

toNonEmpty :: Tree a -> NonEmpty a Source #

maximum :: Ord a => Tree a -> a Source #

minimum :: Ord a => Tree a -> a Source #

head :: Tree a -> a Source #

last :: Tree a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Tree a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Tree a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Tree a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Tree a -> b Source #

Eq1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftEq :: (a -> b -> Bool) -> Tree a -> Tree b -> Bool Source #

Ord1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftCompare :: (a -> b -> Ordering) -> Tree a -> Tree b -> Ordering Source #

Read1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tree a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tree a] Source #

Show1 Tree Source #

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

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

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

Applicative Tree Source # 
Instance details

Defined in Data.Tree

Methods

pure :: a -> Tree a #

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

liftA2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

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

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

Functor Tree Source # 
Instance details

Defined in Data.Tree

Methods

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

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

Monad Tree Source # 
Instance details

Defined in Data.Tree

Methods

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

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

return :: a -> Tree a #

MonadFix Tree Source #

Since: containers-0.5.11

Instance details

Defined in Data.Tree

Methods

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

Foldable Tree Source #

Folds in preorder

Instance details

Defined in Data.Tree

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Tree a -> m #

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

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

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

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

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

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

toList :: Tree a -> [a] #

null :: Tree a -> Bool #

length :: Tree a -> Int #

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

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

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

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

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

Traversable Tree Source # 
Instance details

Defined in Data.Tree

Methods

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

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

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

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

Generic1 Tree Source # 
Instance details

Defined in Data.Tree

Associated Types

type Rep1 Tree

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep1 Tree = D1 ('MetaData "Tree" "Data.Tree" "containers-0.7-inplace" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Tree)))

Methods

from1 :: Tree a -> Rep1 Tree a #

to1 :: Rep1 Tree a -> Tree a #

Lift a => Lift (Tree a :: Type) Source #

Since: containers-0.6.6

Instance details

Defined in Data.Tree

Methods

lift :: Quote m => Tree a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Tree a -> Code m (Tree a) Source #

NFData a => NFData (Tree a) Source # 
Instance details

Defined in Data.Tree

Methods

rnf :: Tree a -> () Source #

Data a => Data (Tree a) Source # 
Instance details

Defined in Data.Tree

Methods

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

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

toConstr :: Tree a -> Constr #

dataTypeOf :: Tree a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Tree a) Source # 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a)

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.7-inplace" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tree a])))

Methods

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

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

Read a => Read (Tree a) Source # 
Instance details

Defined in Data.Tree

Show a => Show (Tree a) Source # 
Instance details

Defined in Data.Tree

Methods

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

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Eq a => Eq (Tree a) Source # 
Instance details

Defined in Data.Tree

Methods

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

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

Ord a => Ord (Tree a) Source #

Since: containers-0.6.5

Instance details

Defined in Data.Tree

Methods

compare :: Tree a -> Tree a -> Ordering #

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

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

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

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

max :: Tree a -> Tree a -> Tree a #

min :: Tree a -> Tree a -> Tree a #

type Rep1 Tree Source #

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep1 Tree = D1 ('MetaData "Tree" "Data.Tree" "containers-0.7-inplace" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Tree)))
type Rep (Tree a) Source #

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.7-inplace" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tree a])))

type Forest a = [Tree a] Source #

This type synonym exists primarily for historical reasons.