[Haskell-cafe] Strange error with type classes + associated types

Brent Yorgey byorgey at seas.upenn.edu
Tue Apr 13 22:48:50 EDT 2010


Hi all,

Consider the following declarations.

> -- from vector-space package:
> (*.*) :: (HasBasis  u, HasTrie  (Basis  u), 
>           HasBasis  v, HasTrie  (Basis  v), 
>           VectorSpace  w, 
>           Scalar  v ~ Scalar  w) 
>       => (v :-*  w) -> (u :-*  v) -> u :-*  w
> 
> -- my code:
> data Affine v = Affine (v :-* v) v
> 
> instance (HasBasis v, HasTrie (Basis v), VectorSpace v) => Monoid (Affine v) where
>   mempty = Affine idL zeroV
>   mappend (Affine a2 b2) (Affine a1 b1) = Affine (a2 *.* a1) (lapply a2 b1 ^+^ b2)

When I try to compile this, I get the following error:

    No instance for (HasTrie (Basis u))
      arising from a use of `*.*' at Diagrams.hs:107:50-58
    Possible fix: add an instance declaration for (HasTrie (Basis u))
    In the first argument of `Affine', namely `(a2 *.* a1)'
    In the expression: Affine (a2 *.* a1) (lapply a2 b1 ^+^ b2)
    In the definition of `mappend':
        mappend (Affine a2 b2) (Affine a1 b1)
                  = Affine (a2 *.* a1) (lapply a2 b1 ^+^ b2)

This seems bizarre to me; it seems like GHC ought to be able to infer
that in my use of (*.*), u,v, and w are all instantiated to the v in
the instance declaration, and hence all the required constraints are
satisfied.  I have no idea why it would be complaining about u ---
there's nothing called u in my instance declaration.

Can someone more well-versed in the intricacies of type checking with
associated types explain this?  Or is this a bug in GHC?

-Brent


More information about the Haskell-Cafe mailing list