module Data.Tree(
	Tree(..), Forest,
	
	drawTree, drawForest,
	
	flatten, levels,
	
	unfoldTree, unfoldForest,
	unfoldTreeM, unfoldForestM,
	unfoldTreeM_BF, unfoldForestM_BF,
    ) where
#ifdef __HADDOCK__
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 Data.Foldable (Foldable(foldMap), toList)
import Data.Traversable (Traversable(traverse))
import Data.Typeable
#ifdef __GLASGOW_HASKELL__
import Data.Data (Data)
#endif
data Tree a   = Node {
		rootLabel :: a,		
		subForest :: Forest a	
	}
#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 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
instance Foldable Tree where
  foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts
drawTree :: Tree String -> String
drawTree  = unlines . draw
drawForest :: Forest String -> String
drawForest  = unlines . map drawTree
draw :: Tree String -> [String]
draw (Node x ts0) = x : drawSubTrees ts0
  where drawSubTrees [] = []
	drawSubTrees [t] =
		"|" : shift "`- " "   " (draw t)
	drawSubTrees (t:ts) =
		"|" : shift "+- " "|  " (draw t) ++ drawSubTrees ts
	shift first other = zipWith (++) (first : repeat other)
flatten :: Tree a -> [a]
flatten t = squish t []
  where squish (Node x ts) xs = x:Prelude.foldr squish xs ts
levels :: Tree a -> [[a]]
levels t = map (map rootLabel) $
		takeWhile (not . null) $
		iterate (concatMap subForest) [t]
unfoldTree :: (b -> (a, [b])) -> b -> Tree a
unfoldTree f b = let (a, bs) = f b in Node a (unfoldForest f bs)
unfoldForest :: (b -> (a, [b])) -> [b] -> Forest a
unfoldForest f = map (unfoldTree f)
unfoldTreeM :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a)
unfoldTreeM f b = do
	(a, bs) <- f b
	ts <- unfoldForestM f bs
	return (Node a ts)
#ifndef __NHC__
unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
#endif
unfoldForestM f = Prelude.mapM (unfoldTreeM f)
unfoldTreeM_BF :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a)
unfoldTreeM_BF f b = liftM getElement $ unfoldForestQ f (singleton b)
  where getElement xs = case viewl xs of
		x :< _ -> x
		EmptyL -> error "unfoldTreeM_BF"
unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
unfoldForestM_BF f = liftM toList . unfoldForestQ f . fromList
unfoldForestQ :: Monad m => (b -> m (a, [b])) -> Seq b -> m (Seq (Tree a))
unfoldForestQ f aQ = case viewl aQ of
	EmptyL -> return empty
	a :< aQ' -> do
		(b, as) <- f a
		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'])
	splitOnto as [] q = (q, as)
	splitOnto as (_:bs) q = case viewr q of
		q' :> a -> splitOnto (a:as) bs q'
		EmptyR -> error "unfoldForestQ"