add System.Posix.Types to default nhc98 build
[haskell-directory.git] / Data / Tree.hs
index 113bc4c..c159a74 100644 (file)
@@ -28,13 +28,18 @@ module Data.Tree(
 import Prelude
 #endif
 
+import Control.Applicative (Applicative(..), (<$>))
 import Control.Monad
+import Data.Monoid (Monoid(..))
 import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList,
                        ViewL(..), ViewR(..), viewl, viewr)
-import qualified Data.Sequence as Seq (foldl)
+import Data.Foldable (Foldable(foldMap), toList)
+import Data.Traversable (Traversable(traverse))
 import Data.Typeable
 
-#include "Typeable.h"
+#ifdef __GLASGOW_HASKELL__
+import Data.Generics.Basics (Data)
+#endif
 
 -- | Multi-way trees, also known as /rose trees/.
 data Tree a   = Node {
@@ -42,21 +47,40 @@ data Tree a   = Node {
                subForest :: Forest a   -- ^ zero or more child trees
        }
 #ifndef __HADDOCK__
+# ifdef __GLASGOW_HASKELL__
+  deriving (Eq, Read, Show, Data)
+# else
   deriving (Eq, Read, Show)
+# endif
 #else /* __HADDOCK__ (which can't figure these out by itself) */
 instance Eq a => Eq (Tree a)
 instance Read a => Read (Tree a)
 instance Show a => Show (Tree a)
+instance Data a => Data (Tree a)
 #endif
 type Forest a = [Tree a]
 
+#include "Typeable.h"
 INSTANCE_TYPEABLE1(Tree,treeTc,"Tree")
 
 instance Functor Tree where
-  fmap = mapTree
+  fmap f (Node x ts) = Node (f x) (map (fmap f) ts)
+
+instance Applicative Tree where
+  pure x = Node x []
+  Node f tfs <*> tx@(Node x txs) =
+    Node (f x) (map (f <$>) txs ++ map (<*> tx) tfs)
+
+instance Monad Tree where
+  return x = Node x []
+  Node x ts >>= f = Node x' (ts' ++ map (>>= f) ts)
+    where Node x' ts' = f x
+
+instance Traversable Tree where
+  traverse f (Node x ts) = Node <$> f x <*> traverse (traverse f) ts
 
-mapTree              :: (a -> b) -> (Tree a -> Tree b)
-mapTree f (Node x ts) = Node (f x) (map (mapTree f) ts)
+instance Foldable Tree where
+  foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts
 
 -- | Neat 2-dimensional drawing of a tree.
 drawTree :: Tree String -> String
@@ -79,7 +103,7 @@ draw (Node x ts0) = x : drawSubTrees ts0
 -- | The elements of a tree in pre-order.
 flatten :: Tree a -> [a]
 flatten t = squish t []
-  where squish (Node x ts) xs = x:foldr squish xs ts
+  where squish (Node x ts) xs = x:Prelude.foldr squish xs ts
 
 -- | Lists of nodes at each level of the tree.
 levels :: Tree a -> [[a]]
@@ -106,7 +130,7 @@ unfoldTreeM f b = do
 #ifndef __NHC__
 unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
 #endif
-unfoldForestM f = mapM (unfoldTreeM f)
+unfoldForestM f = Prelude.mapM (unfoldTreeM f)
 
 -- | Monadic tree builder, in breadth-first order,
 -- using an algorithm adapted from
@@ -123,9 +147,7 @@ unfoldTreeM_BF f b = liftM getElement $ unfoldForestQ f (singleton b)
 -- /Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design/,
 -- by Chris Okasaki, /ICFP'00/.
 unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
-unfoldForestM_BF f = liftM toRevList . unfoldForestQ f . fromList
-  where toRevList :: Seq c -> [c]
-       toRevList = Seq.foldl (flip (:)) []
+unfoldForestM_BF f = liftM toList . unfoldForestQ f . fromList
 
 -- takes a sequence (queue) of seeds
 -- produces a sequence (reversed queue) of trees of the same length
@@ -134,7 +156,7 @@ unfoldForestQ f aQ = case viewl aQ of
        EmptyL -> return empty
        a :< aQ -> do
                (b, as) <- f a
-               tQ <- unfoldForestQ f (foldl (|>) aQ as)
+               tQ <- unfoldForestQ f (Prelude.foldl (|>) aQ as)
                let (tQ', ts) = splitOnto [] as tQ
                return (Node b ts <| tQ')
   where splitOnto :: [a'] -> [b'] -> Seq a' -> (Seq a', [a'])