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