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