
I agree with prior discussion on this list that adding contexts to datatype declarations seems to be more trouble than its worth, since these contexts just have to be added again to every function using the datatype. However, I have often wondered: why do function *have* to have these contexts? What would it affect in the language if we made the contexts be implicit, so that if we have data Datatype a = Context a => Datatype a then for function declarations f :: D a -> ... the context "Context a" is automatically asserted by the compiler? Cheers, Greg

There are two types of datatype contexts; haskell'98 contexts (which I
think are terrible), and GHC existential contexts (which I like):
class C a where runC :: a -> Int
data C a => T1 a = D1 a
All this does is add a context to the D1 *constructor*; that is:
-- D1 :: C a => a -> T1 a
But extracting a value of this type does nothing:
foo :: T1 a -> Int
foo (D1 a) = runC a -- compile error
However, putting the context on the RHS as you have done works in GHC
and does "the right thing"; pattern matching on that constructor now
brings the class into scope. You can think of the datatype has having
another field which is "proof that a is a member of C":
{-# LANGUAGE ExistentialQuantification #-}
data T2 a = C a => D2 a
-- D2 :: C a => a -> T2 a -- same as D1
bar :: T2 a -> Int
bar (D2 a) = runC a -- works
-- ryan
On Mon, Jul 26, 2010 at 7:48 AM, Gregory Crosswhite
I agree with prior discussion on this list that adding contexts to datatype declarations seems to be more trouble than its worth, since these contexts just have to be added again to every function using the datatype. However, I have often wondered: why do function *have* to have these contexts? What would it affect in the language if we made the contexts be implicit, so that if we have
data Datatype a = Context a => Datatype a
then for function declarations
f :: D a -> ...
the context "Context a" is automatically asserted by the compiler?
Cheers, Greg
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh, now I see! I knew about (and have used) existential contexts, but somehow I hadn't made the connection that in a sense they are already equivalent to our intuition for Haskell 98 contexts "done right". :-) Thanks! Any chance of seeing them in Haskell'11? Cheers, Greg On 07/26/10 10:44, Ryan Ingram wrote:
There are two types of datatype contexts; haskell'98 contexts (which I think are terrible), and GHC existential contexts (which I like):
class C a where runC :: a -> Int data C a => T1 a = D1 a
All this does is add a context to the D1 *constructor*; that is: -- D1 :: C a => a -> T1 a
But extracting a value of this type does nothing:
foo :: T1 a -> Int foo (D1 a) = runC a -- compile error
However, putting the context on the RHS as you have done works in GHC and does "the right thing"; pattern matching on that constructor now brings the class into scope. You can think of the datatype has having another field which is "proof that a is a member of C":
{-# LANGUAGE ExistentialQuantification #-} data T2 a = C a => D2 a -- D2 :: C a => a -> T2 a -- same as D1
bar :: T2 a -> Int bar (D2 a) = runC a -- works
-- ryan
On Mon, Jul 26, 2010 at 7:48 AM, Gregory Crosswhite
wrote: I agree with prior discussion on this list that adding contexts to datatype declarations seems to be more trouble than its worth, since these contexts just have to be added again to every function using the datatype. However, I have often wondered: why do function *have* to have these contexts? What would it affect in the language if we made the contexts be implicit, so that if we have
data Datatype a = Context a => Datatype a
then for function declarations
f :: D a -> ...
the context "Context a" is automatically asserted by the compiler?
Cheers, Greg
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2010/7/26 Ryan Ingram
There are two types of datatype contexts; haskell'98 contexts (which I think are terrible), and GHC existential contexts (which I like):
See also "GADT-style" data type declarations [1] and full GADT's [2], which both behave like GHC existential contexts mentioned above: pattern matching on them makes available the context constraint. Dominique Footnotes: [1] http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions... [2] http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions...
participants (3)
-
Dominique Devriese
-
Gregory Crosswhite
-
Ryan Ingram