
14 Oct
2009
14 Oct
'09
6:07 p.m.
* Martijn van Steenbergen
Dear café,
{-# LANGUAGE Rank2Types #-} {-# LANGUAGE ImpredicativeTypes #-}
type Void = forall a. a
newtype Mono a = Mono { runMono :: [Void] }
beep :: Mono a -> Mono a beep (Mono vs) = Mono (map undefined vs)
Compiling this with GHC results in:
Monotype.hs:9:28: Cannot match a monotype with `Void' Expected type: Void Inferred type: a
What does this error mean and why does the code not compile?
It works if you annotate the type of undefined: beep (Mono vs) = Mono (map (undefined :: Void -> Void) vs) -- Roman I. Cheplyaka :: http://ro-che.info/ "Don't let school get in the way of your education." - Mark Twain