module Text.LaTeX.Packages.Trees (
Tree (..)
) where
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
import Data.Foldable
import Data.Traversable
#endif
import Control.Applicative
data Tree a =
Leaf a
| Node (Maybe a) [Tree a]
instance Functor Tree where
fmap f (Leaf a) = Leaf $ f a
fmap f (Node ma ts) = Node (fmap f ma) $ fmap (fmap f) ts
instance Foldable Tree where
foldMap f (Leaf a) = f a
foldMap f (Node ma ts) = foldMap f ma `mappend` mconcat (fmap (foldMap f) ts)
instance Traversable Tree where
sequenceA (Leaf fa) = Leaf <$> fa
sequenceA (Node mfa ts) = liftA2 Node (sequenceA mfa) $ sequenceA $ fmap sequenceA ts