-- | -- Module : Data.Trees.MTree -- Copyright : Rahul Gopinath -- License : PublicDomain -- -- Maintainer : Rahul Gopinath (gopinath@eecs.oregonstate.edu) -- Stability : experimental -- Portability : portable -- -- This Haskell library provides an implementation of a tree data -- type with meta data in the nodes and content in the leaves. -- module Data.Trees.MTree where import qualified Data.Bifunctor as Bi import qualified Data.Bitraversable as Bit import qualified Data.Traversable as Tr import qualified Data.Foldable as Fl import qualified Data.Bifoldable as Bif import qualified Data.Monoid as Monoid (mappend, mempty, mconcat, Monoid) import Control.Applicative -- | -- | The @Tree m c@ is a tree structure with metadata in the nodes -- | and metadata and content in the leaves. data Tree m c = Leaf { meta :: m, content :: c } | Node { meta :: m, trees :: [Tree m c]} deriving (Show,Eq) instance Bi.Bifunctor (Tree) where bimap f1 f2 (Leaf m c) = Leaf (f1 m) (f2 c) bimap f1 f2 (Node m l) = Node (f1 m) $ map (Bi.bimap f1 f2) l instance Bif.Bifoldable Tree where bifoldMap f g (Leaf m c) = f m `Monoid.mappend` g c bifoldMap f g (Node m l) = f m `Monoid.mappend` Fl.foldMap (Bif.bifoldMap f g) l instance Bit.Bitraversable Tree where bitraverse f g (Leaf m c) = Leaf <$> f m <*> g c bitraverse f g (Node m l) = Node <$> f m <*> Tr.traverse (Bit.bitraverse f g) l