See our previous discussion on this topic here: http://www.nabble.com/Fwd:-Unification-for-rank-N-types-td23942179.html

Thanks,
Vladimir

On Wed, Oct 14, 2009 at 10:35 PM, Martijn van Steenbergen <martijn@van.steenbergen.nl> wrote:
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.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe