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