[Haskell-cafe] Question, re: failed attempt at constraining a Traversable instance.

David Banas capn.freako at gmail.com
Mon Feb 1 13:28:31 UTC 2016


Hi all,

I’m trying to do this:

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’m being told this:

The first argument of ‘Traversable’ should have kind ‘* -> *’, but ‘Tree (f a)’ has kind ‘*’
In the instance declaration for ‘Traversable (Tree (f a))’

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?

Thanks,
-db

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160201/fe469427/attachment.html>


More information about the Haskell-Cafe mailing list