[Haskell-cafe] Class Instance with ExistentialQuantification

Roman Cheplyaka roma at ro-che.info
Tue Jan 7 10:18:12 UTC 2014


* Andrew Gibiansky <andrew.gibiansky at gmail.com> [2014-01-06 22:17:21-0500]
> Why is the following not allowed?
> 
> {-# LANGUAGE ExistentialQuantification, ExplicitForAll, RankNTypes,
> FlexibleInstances #-}
> 
> class Class a where
>   test :: a -> Bool
> 
> instance Class (forall m. m -> m) where
>   test _ = True
> 
> main = do
>   putStrLn $ test id
> 
> Is there a reason that this is forbidden? Just curious.

I believe the rule is that all constraints (including class constraints)
range over monotypes.

What are you trying to achieve?

You can do this, for example:

  newtype Poly = Poly (forall a . a -> a)
  instance Class Poly where test = const True

  main = print $ test $ Poly id

BTW, this has nothing to do with ExistentialQuantification.

Roman
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: Digital signature
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140107/e80498be/attachment.sig>


More information about the Haskell-Cafe mailing list