Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / Data / Tree.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Tree
4 -- Copyright   :  (c) The University of Glasgow 2002
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- Multi-way trees (/aka/ rose trees) and forests.
12 --
13 -----------------------------------------------------------------------------
14
15 module Data.Tree(
16         Tree(..), Forest,
17         -- * Two-dimensional drawing
18         drawTree, drawForest,
19         -- * Extraction
20         flatten, levels,
21         -- * Building trees
22         unfoldTree, unfoldForest,
23         unfoldTreeM, unfoldForestM,
24         unfoldTreeM_BF, unfoldForestM_BF,
25     ) where
26
27 #ifdef __HADDOCK__
28 import Prelude
29 #endif
30
31 import Control.Applicative (Applicative(..), (<$>))
32 import Control.Monad
33 import Data.Monoid (Monoid(..))
34 import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList,
35                         ViewL(..), ViewR(..), viewl, viewr)
36 import Data.Foldable (Foldable(foldMap), toList)
37 import Data.Traversable (Traversable(traverse))
38 import Data.Typeable
39
40 #ifdef __GLASGOW_HASKELL__
41 import Data.Generics.Basics (Data)
42 #endif
43
44 -- | Multi-way trees, also known as /rose trees/.
45 data Tree a   = Node {
46                 rootLabel :: a,         -- ^ label value
47                 subForest :: Forest a   -- ^ zero or more child trees
48         }
49 #ifndef __HADDOCK__
50 # ifdef __GLASGOW_HASKELL__
51   deriving (Eq, Read, Show, Data)
52 # else
53   deriving (Eq, Read, Show)
54 # endif
55 #else /* __HADDOCK__ (which can't figure these out by itself) */
56 instance Eq a => Eq (Tree a)
57 instance Read a => Read (Tree a)
58 instance Show a => Show (Tree a)
59 instance Data a => Data (Tree a)
60 #endif
61 type Forest a = [Tree a]
62
63 #include "Typeable.h"
64 INSTANCE_TYPEABLE1(Tree,treeTc,"Tree")
65
66 instance Functor Tree where
67   fmap f (Node x ts) = Node (f x) (map (fmap f) ts)
68
69 instance Applicative Tree where
70   pure x = Node x []
71   Node f tfs <*> tx@(Node x txs) =
72     Node (f x) (map (f <$>) txs ++ map (<*> tx) tfs)
73
74 instance Monad Tree where
75   return x = Node x []
76   Node x ts >>= f = Node x' (ts' ++ map (>>= f) ts)
77     where Node x' ts' = f x
78
79 instance Traversable Tree where
80   traverse f (Node x ts) = Node <$> f x <*> traverse (traverse f) ts
81
82 instance Foldable Tree where
83   foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts
84
85 -- | Neat 2-dimensional drawing of a tree.
86 drawTree :: Tree String -> String
87 drawTree  = unlines . draw
88
89 -- | Neat 2-dimensional drawing of a forest.
90 drawForest :: Forest String -> String
91 drawForest  = unlines . map drawTree
92
93 draw :: Tree String -> [String]
94 draw (Node x ts0) = x : drawSubTrees ts0
95   where drawSubTrees [] = []
96         drawSubTrees [t] =
97                 "|" : shift "`- " "   " (draw t)
98         drawSubTrees (t:ts) =
99                 "|" : shift "+- " "|  " (draw t) ++ drawSubTrees ts
100
101         shift first other = zipWith (++) (first : repeat other)
102
103 -- | The elements of a tree in pre-order.
104 flatten :: Tree a -> [a]
105 flatten t = squish t []
106   where squish (Node x ts) xs = x:Prelude.foldr squish xs ts
107
108 -- | Lists of nodes at each level of the tree.
109 levels :: Tree a -> [[a]]
110 levels t = map (map rootLabel) $
111                 takeWhile (not . null) $
112                 iterate (concatMap subForest) [t]
113
114 -- | Build a tree from a seed value
115 unfoldTree :: (b -> (a, [b])) -> b -> Tree a
116 unfoldTree f b = let (a, bs) = f b in Node a (unfoldForest f bs)
117
118 -- | Build a forest from a list of seed values
119 unfoldForest :: (b -> (a, [b])) -> [b] -> Forest a
120 unfoldForest f = map (unfoldTree f)
121
122 -- | Monadic tree builder, in depth-first order
123 unfoldTreeM :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a)
124 unfoldTreeM f b = do
125         (a, bs) <- f b
126         ts <- unfoldForestM f bs
127         return (Node a ts)
128
129 -- | Monadic forest builder, in depth-first order
130 #ifndef __NHC__
131 unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
132 #endif
133 unfoldForestM f = Prelude.mapM (unfoldTreeM f)
134
135 -- | Monadic tree builder, in breadth-first order,
136 -- using an algorithm adapted from
137 -- /Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design/,
138 -- by Chris Okasaki, /ICFP'00/.
139 unfoldTreeM_BF :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a)
140 unfoldTreeM_BF f b = liftM getElement $ unfoldForestQ f (singleton b)
141   where getElement xs = case viewl xs of
142                 x :< _ -> x
143                 EmptyL -> error "unfoldTreeM_BF"
144
145 -- | Monadic forest builder, in breadth-first order,
146 -- using an algorithm adapted from
147 -- /Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design/,
148 -- by Chris Okasaki, /ICFP'00/.
149 unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
150 unfoldForestM_BF f = liftM toList . unfoldForestQ f . fromList
151
152 -- takes a sequence (queue) of seeds
153 -- produces a sequence (reversed queue) of trees of the same length
154 unfoldForestQ :: Monad m => (b -> m (a, [b])) -> Seq b -> m (Seq (Tree a))
155 unfoldForestQ f aQ = case viewl aQ of
156         EmptyL -> return empty
157         a :< aQ -> do
158                 (b, as) <- f a
159                 tQ <- unfoldForestQ f (Prelude.foldl (|>) aQ as)
160                 let (tQ', ts) = splitOnto [] as tQ
161                 return (Node b ts <| tQ')
162   where splitOnto :: [a'] -> [b'] -> Seq a' -> (Seq a', [a'])
163         splitOnto as [] q = (q, as)
164         splitOnto as (_:bs) q = case viewr q of
165                 q' :> a -> splitOnto (a:as) bs q'
166                 EmptyR -> error "unfoldForestQ"