d04fe3d92ca259471553cb2bc80e9b81f51bb8e3
[ghc-base.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 #ifndef __NHC__
24         unfoldTreeM, unfoldForestM,
25 #endif
26         unfoldTreeM_BF, unfoldForestM_BF,
27     ) where
28
29 #ifdef __HADDOCK__
30 import Prelude
31 #endif
32
33 import Control.Monad
34 import Data.Maybe
35 import Data.Queue
36
37 -- | Multi-way trees, also known as /rose trees/.
38 data Tree a   = Node {
39                 rootLabel :: a,         -- ^ label value
40                 subForest :: Forest a   -- ^ zero or more child trees
41         }
42 #ifndef __HADDOCK__
43   deriving (Eq, Read, Show)
44 #else /* __HADDOCK__ (which can't figure these out by itself) */
45 instance Eq a => Eq (Tree a)
46 instance Read a => Read (Tree a)
47 instance Show a => Show (Tree a)
48 #endif
49 type Forest a = [Tree a]
50
51 instance Functor Tree where
52   fmap = mapTree
53
54 mapTree              :: (a -> b) -> (Tree a -> Tree b)
55 mapTree f (Node x ts) = Node (f x) (map (mapTree f) ts)
56
57 -- | Neat 2-dimensional drawing of a tree.
58 drawTree :: Tree String -> String
59 drawTree  = unlines . draw
60
61 -- | Neat 2-dimensional drawing of a forest.
62 drawForest :: Forest String -> String
63 drawForest  = unlines . map drawTree
64
65 draw :: Tree String -> [String]
66 draw (Node x ts0) = x : drawSubTrees ts0
67   where drawSubTrees [] = []
68         drawSubTrees [t] =
69                 "|" : shift "`- " "   " (draw t)
70         drawSubTrees (t:ts) =
71                 "|" : shift "+- " "|  " (draw t) ++ drawSubTrees ts
72
73         shift first other = zipWith (++) (first : repeat other)
74
75 -- | The elements of a tree in pre-order.
76 flatten :: Tree a -> [a]
77 flatten t = squish t []
78   where squish (Node x ts) xs = x:foldr squish xs ts
79
80 -- | Lists of nodes at each level of the tree.
81 levels :: Tree a -> [[a]]
82 levels t = map (map rootLabel) $
83                 takeWhile (not . null) $
84                 iterate (concatMap subForest) [t]
85
86 -- | Build a tree from a seed value
87 unfoldTree :: (b -> (a, [b])) -> b -> Tree a
88 unfoldTree f b = let (a, bs) = f b in Node a (unfoldForest f bs)
89
90 -- | Build a forest from a list of seed values
91 unfoldForest :: (b -> (a, [b])) -> [b] -> Forest a
92 unfoldForest f = map (unfoldTree f)
93
94 #ifndef __NHC__
95 -- | Monadic tree builder, in depth-first order
96 unfoldTreeM :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a)
97 unfoldTreeM f b = do
98         (a, bs) <- f b
99         ts <- unfoldForestM f bs
100         return (Node a ts)
101
102 -- | Monadic forest builder, in depth-first order
103 unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
104 unfoldForestM f = mapM (unfoldTreeM f)
105 #endif
106
107 -- | Monadic tree builder, in breadth-first order,
108 -- using an algorithm adapted from
109 -- /Breadth­First Numbering: Lessons from a Small Exercise in Algorithm Design/,
110 -- by Chris Okasaki, /ICFP'00/.
111 unfoldTreeM_BF :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a)
112 unfoldTreeM_BF f b = liftM (fst . fromJust . deQueue) $
113         unfoldForestQ f (listToQueue [b])
114
115 -- | Monadic forest builder, in breadth-first order,
116 -- using an algorithm adapted from
117 -- /Breadth­First Numbering: Lessons from a Small Exercise in Algorithm Design/,
118 -- by Chris Okasaki, /ICFP'00/.
119 unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
120 unfoldForestM_BF f = liftM (reverseOnto []) . unfoldForestQ f . listToQueue
121   where reverseOnto :: [a] -> Queue a -> [a]
122         reverseOnto as q = case deQueue q of
123                 Nothing -> as
124                 Just (a, q') -> reverseOnto (a:as) q'
125
126 -- takes a queue of seeds
127 -- produces a queue of trees of the same length, but in the reverse order
128 unfoldForestQ :: Monad m => (b -> m (a, [b])) -> Queue b -> m (Queue (Tree a))
129 unfoldForestQ f aQ = case deQueue aQ of
130         Nothing -> return emptyQueue
131         Just (a, aQ) -> do
132                 (b, as) <- f a
133                 tQ <- unfoldForestQ f (foldl addToQueue aQ as)
134                 let (ts, tQ') = splitOnto [] as tQ
135                 return (addToQueue tQ' (Node b ts))
136   where splitOnto :: [a] -> [b] -> Queue a -> ([a], Queue a)
137         splitOnto as [] q = (as, q)
138         splitOnto as (_:bs) q = case fromJust (deQueue q) of
139                 (a, q') -> splitOnto (a:as) bs q'