#if __GLASGOW_HASKELL__
#endif
#include "containers.h"
module Data.Tree(
Tree(..)
, Forest
, unfoldTree
, unfoldForest
, unfoldTreeM
, unfoldForestM
, unfoldTreeM_BF
, unfoldForestM_BF
, foldTree
, flatten
, levels
, drawTree
, drawForest
) where
#if MIN_VERSION_base(4,8,0)
import Data.Foldable (toList)
import Control.Applicative (Applicative(..), liftA2)
#else
import Control.Applicative (Applicative(..), liftA2, (<$>))
import Data.Foldable (Foldable(foldMap), toList)
import Data.Monoid (Monoid(..))
import Data.Traversable (Traversable(traverse))
#endif
import Control.Monad (liftM)
import Control.Monad.Fix (MonadFix (..), fix)
import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList,
ViewL(..), ViewR(..), viewl, viewr)
import Data.Typeable
import Control.DeepSeq (NFData(rnf))
#ifdef __GLASGOW_HASKELL__
import Data.Data (Data)
import GHC.Generics (Generic, Generic1)
#endif
import Control.Monad.Zip (MonadZip (..))
#if MIN_VERSION_base(4,8,0)
import Data.Coerce
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Functor.Classes
#endif
#if (!MIN_VERSION_base(4,11,0)) && MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup (..))
#endif
#if !MIN_VERSION_base(4,8,0)
import Data.Functor ((<$))
#endif
data Tree a = Node {
rootLabel :: a,
subForest :: [Tree a]
}
#ifdef __GLASGOW_HASKELL__
deriving ( Eq
, Ord
, Read
, Show
, Data
, Generic
, Generic1
)
#else
deriving (Eq, Ord, Read, Show)
#endif
type Forest a = [Tree a]
#if MIN_VERSION_base(4,9,0)
instance Eq1 Tree where
liftEq eq = leq
where
leq (Node a fr) (Node a' fr') = eq a a' && liftEq leq fr fr'
instance Ord1 Tree where
liftCompare cmp = lcomp
where
lcomp (Node a fr) (Node a' fr') = cmp a a' <> liftCompare lcomp fr fr'
instance Show1 Tree where
liftShowsPrec shw shwl p (Node a fr) = showParen (p > 10) $
showString "Node {rootLabel = " . shw 0 a . showString ", " .
showString "subForest = " . liftShowList shw shwl fr .
showString "}"
instance Read1 Tree where
liftReadsPrec rd rdl p = readParen (p > 10) $
\s -> do
("Node", s1) <- lex s
("{", s2) <- lex s1
("rootLabel", s3) <- lex s2
("=", s4) <- lex s3
(a, s5) <- rd 0 s4
(",", s6) <- lex s5
("subForest", s7) <- lex s6
("=", s8) <- lex s7
(fr, s9) <- liftReadList rd rdl s8
("}", s10) <- lex s9
pure (Node a fr, s10)
#endif
INSTANCE_TYPEABLE1(Tree)
instance Functor Tree where
fmap = fmapTree
x <$ Node _ ts = Node x (map (x <$) ts)
fmapTree :: (a -> b) -> Tree a -> Tree b
fmapTree f (Node x ts) = Node (f x) (map (fmapTree f) ts)
#if MIN_VERSION_base(4,8,0)
#endif
instance Applicative Tree where
pure x = Node x []
Node f tfs <*> tx@(Node x txs) =
Node (f x) (map (f <$>) txs ++ map (<*> tx) tfs)
#if MIN_VERSION_base(4,10,0)
liftA2 f (Node x txs) ty@(Node y tys) =
Node (f x y) (map (f x <$>) tys ++ map (\tx -> liftA2 f tx ty) txs)
#endif
Node x txs <* ty@(Node _ tys) =
Node x (map (x <$) tys ++ map (<* ty) txs)
Node _ txs *> ty@(Node y tys) =
Node y (tys ++ map (*> ty) txs)
instance Monad Tree where
return = pure
Node x ts >>= f = case f x of
Node x' ts' -> Node x' (ts' ++ map (>>= f) ts)
instance MonadFix Tree where
mfix = mfixTree
mfixTree :: (a -> Tree a) -> Tree a
mfixTree f
| Node a children <- fix (f . rootLabel)
= Node a (zipWith (\i _ -> mfixTree ((!! i) . subForest . f))
[0..] children)
instance Traversable Tree where
traverse f (Node x ts) = liftA2 Node (f x) (traverse (traverse f) ts)
instance Foldable Tree where
foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts
#if MIN_VERSION_base(4,8,0)
null _ = False
toList = flatten
#endif
instance NFData a => NFData (Tree a) where
rnf (Node x ts) = rnf x `seq` rnf ts
instance MonadZip Tree where
mzipWith f (Node a as) (Node b bs)
= Node (f a b) (mzipWith (mzipWith f) as bs)
munzip (Node (a, b) ts) = (Node a as, Node b bs)
where (as, bs) = munzip (map munzip ts)
drawTree :: Tree String -> String
drawTree = unlines . draw
drawForest :: [Tree String] -> String
drawForest = unlines . map drawTree
draw :: Tree String -> [String]
draw (Node x ts0) = lines 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]
foldTree :: (a -> [b] -> b) -> Tree a -> b
foldTree f = go where
go (Node x ts) = f x (map go ts)
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] -> [Tree 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)
unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m ([Tree a])
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 ([Tree 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"