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

Adam Gundry adam at well-typed.com
Mon Feb 1 17:53:50 UTC 2016


Hi,

On 01/02/16 13:28, David Banas wrote:
> I’m trying to do this:
> 
>     data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
> 
> [...]
>
>     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?

Being Traversable (or indeed a Functor) is a property of type
constructors (of kind * -> *), not of types (of kind *).  In much the
same way, the list type constructor [] is Traversable, but not the
particular list type [Int].

The explicitly quantified type of `traverse` for a particular
`Traversable t` is this:

    forall f a b . Applicative f => (a -> f b) -> t a -> f (t b)

Notice that this involves `t a` and `t b` where `a` and `b` are
polymorphic type variables, chosen by the caller of `traverse`. There's
no way to constrain the particular types that might be used to
instantiate those type variables.

What are you really trying to do? If you'd like to write an instance for
`Traversable Tree`, the haddocks for Traversable might help. :-) Or
perhaps you'd like to use something like `Traversable (Compose Tree f)`?

Hope this helps,

Adam


-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


More information about the Haskell-Cafe mailing list