#2893: Implement "Quantified contexts" proposal
---------------------------------+------------------------------------------
Reporter: porges | Owner:
Type: feature request | Status: new
Priority: normal | Milestone: _|_
Component: Compiler | Version: 6.10.1
Keywords: proposal | Testcase:
Blockedby: | Difficulty: Unknown
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by batterseapower):
As the blog post points out (and I recently rediscovered) GHC already
supports this feature in a more elaborate form. This works:
~~~
{-# LANGUAGE GADTs, Rank2Types, FlexibleContexts #-}
class Foo a where
foo :: a -> String
instance Foo [b] where
foo = show . length
data FooDict a where
FooDict :: Foo a => FooDict a
f :: (forall b. FooDict [b]) -> String
f FooDict = foo "Hello" ++ foo [1, 2, 3]
use_foo :: String
use_foo = f FooDict
~~~
But this is rejected:
~~~
g :: (forall b. Foo [b]) => String
g = foo "Hello" ++ foo [1, 2, 3]
use_foo' :: String
use_foo' = g
~~~
So there doesn't seem to be a fundamental difficulty here.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2893#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs