[Haskell-cafe] Monotype error

Martijn van Steenbergen martijn at van.steenbergen.nl
Wed Oct 14 14:35:06 EDT 2009


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?

Thanks!

Martijn.


More information about the Haskell-Cafe mailing list