[Haskell-cafe] Strange type error with associated type synonyms

Simon Peyton-Jones simonpj at microsoft.com
Tue Apr 7 10:45:08 EDT 2009


| Here is a variation to make this point clearer:
|
| {-# LANGUAGE NoMonomorphismRestriction #-}
| {-# LANGUAGE TypeFamilies, ScopedTypeVariables #-}
|
| class Fun d where
|     type Memo d :: * -> *
|     abst :: (d -> a) -> Memo d a
|     appl :: Memo d a -> (d -> a)
|
| f = abst . appl
|
| -- f' :: forall d a. (Fun d) => Memo d a -> Memo d a
| f' = abst . (id :: (d->a)->(d->a)) . appl
|
| There is a perfectly valid type signature for f', as given in
| comment, but GHCi gives an incorrect one (the same as for f):
|
| *Main> :browse Main
| class Fun d where
|   abst :: (d -> a) -> Memo d a
|   appl :: Memo d a -> d -> a
| f :: (Fun d) => Memo d a -> Memo d a
| f' :: (Fun d) => Memo d a -> Memo d a

I'm missing something here.  Those types are identical to the one given in your type signature for f' above, save that the forall is suppressed (because you are allowed to omit it, and GHC generally does when printing types).

I must be missing the point.

Simon


More information about the Haskell-Cafe mailing list