data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
instance Functor Tree where
fmap g Empty = Empty
fmap g (Leaf x) = Leaf (g x)
fmap g (Node t1 x t2) = Node (fmap g t1) (g x) (fmap g t2)
instance Foldable Tree where
foldMap f Empty = mempty
foldMap f (Leaf x) = f x
foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
instance (Monoid (f (Tree a))) => Traversable (Tree (f a)) where
sequenceA Empty = pure Empty
sequenceA (Leaf f) = Leaf <$> f
sequenceA (Node t1 f t2) = (sequenceA t1) `mappend` (Leaf <$> f) `mappend` (sequenceA t2)
And I don’t quite understand what I’m asking for that’s forbidden.
Is it that I’m trying to declare that only a certain subset of Trees are Traversable, and that’s not okay? It’s got to be all Trees or no Trees are Traversable?