[Haskell-cafe] Class Instance with ExistentialQuantification

Joachim Breitner mail at joachim-breitner.de
Tue Jan 7 15:16:15 UTC 2014


Hi,

is it not allowed simply because none has needed it yet, or is there a
deeper theoretical problem with it?

I’m asking because the implementation of Coercible behaves as if there
is an instance
    instance forall a. (Coercible (t1 a) (t2 a)) => Coercible (forall a. t1 a) (forall a. t2 a)
and if were theoretically dubious, I’d like to know about it :-)

Greetings,
Joachim

Am Dienstag, den 07.01.2014, 10:11 -0500 schrieb Andrew Gibiansky:
> Ah, I see. I wasn't aware that constraints had to be over monotypes. I
> figured that since you could write a function 
> 
> 
> f :: (forall a. a -> a) -> Bool
> 
> 
> Then you could also do similar things with a class.
> 
> 
> (The reason I was doing this was that I wanted a typeclass to match
> something like "return 'a'" without using IncoherentInstances or other
> sketchiness, and found that trying to have a typeclass with an
> instance for 'forall m. Monad m => m Char` gave me this error.)
> 
> 
> Thanks!
> Andrew
> 
> 
> On Tue, Jan 7, 2014 at 5:18 AM, Roman Cheplyaka <roma at ro-che.info>
> wrote:
>         * 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
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Joachim “nomeata” Breitner
  mail at joachim-breitner.dehttp://www.joachim-breitner.de/
  Jabber: nomeata at joachim-breitner.de  • GPG-Key: 0x4743206C
  Debian Developer: nomeata at debian.org
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140107/8801ee50/attachment.sig>


More information about the Haskell-Cafe mailing list