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

Stephen Tetley stephen.tetley at gmail.com
Wed Apr 14 04:51:52 EDT 2010


On 14 April 2010 03:48, Brent Yorgey <byorgey at seas.upenn.edu> wrote:

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

Hi Brent

Maybe you can't compose linear maps of the same type, and thus can't
build a valid monoid instance?

If you take the definition of append out out the class - GHCi will
give it a type:

> append (Affine a2 b2) (Affine a1 b1) = Affine (a2 *.* a1) (lapply a2 b1 ^+^ b2)

*VectorSpace> :t append
append
  :: (Scalar v ~ Scalar v1,
      Basis v ~ Basis u,
      Basis v1 ~ Basis v,
      VectorSpace v1,
      HasTrie (Basis v),
      HasBasis v,
      HasBasis u) =>
     Affine v1 -> Affine v -> Affine v1

If you add that type back to the file containing append it no longer
type checks...

VectorSpaceTest.hs:44:54:
    Couldn't match expected type `Basis u'
           against inferred type `Basis u1'
      NB: `Basis' is a type function, and may not be injective
      Expected type: u :-* v
      Inferred type: v :-* v
    In the second argument of `(*.*)', namely `a1'
    In the first argument of `Affine', namely `(a2 *.* a1)'
Failed, modules loaded: none.

[ It also has the problem that its type isn't compatible with monoidal
mappend anyway ]

You can get empty to type check with this signature:
empty :: (HasTrie u, u ~ Basis v, HasBasis v) => Affine v

But trying to get append to type check with the same class constraints...

append :: (HasTrie u, u ~ Basis v, HasBasis v)
       => Affine v -> Affine v -> Affine v

... gets another error where the inferred type of 'LinearMap' is from
one type to the same type:


VectorSpaceTest.hs:33:54:
    Couldn't match expected type `Basis u' against inferred type `u1'
      `u1' is a rigid type variable bound by
           the type signature for `append' at VectorSpace.hs:31:19
      NB: `Basis' is a type function, and may not be injective
      Expected type: u :-* v
      Inferred type: v :-* v
    In the second argument of `(*.*)', namely `a1'
    In the first argument of `Affine', namely `(a2 *.* a1)'
Failed, modules loaded: none.


More information about the Haskell-Cafe mailing list