Re: How to fix DatatypeContexts?

2013-07-18 Thread Christopher Done
Why not this? data Pair = forall a. Eq a = Pair {x::a, y::a} equal :: Pair - Bool equal (Pair x y) = x == y ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: How to fix DatatypeContexts?

2013-07-18 Thread Christopher Done
Hm, also, with equality constraints you can make the type parametrized, too: data Pair a' = forall a. (a ~ a', Eq a) = Pair {x::a, y::a} equal :: Pair a - Bool equal (Pair x y) = x == y On 18 July 2013 13:00, Christopher Done chrisd...@gmail.com wrote: Why not this? data Pair = forall a. Eq

Re: How to fix DatatypeContexts?

2013-07-18 Thread Sjoerd Visscher
I'd use GADT syntax for this: {-# LANGUAGE GADTs #-} data Pair a where Pair :: Eq a = {x::a, y::a} - Pair a Sjoerd On Jul 18, 2013, at 1:05 PM, Christopher Done chrisd...@gmail.com wrote: Hm, also, with equality constraints you can make the type parametrized, too: data Pair a' = forall a.

Re: How to fix DatatypeContexts?

2013-07-18 Thread Christopher Done
Good point, classic use-case for GADTs. On 18 July 2013 13:11, Sjoerd Visscher sjo...@w3future.com wrote: I'd use GADT syntax for this: {-# LANGUAGE GADTs #-} data Pair a where Pair :: Eq a = {x::a, y::a} - Pair a Sjoerd On Jul 18, 2013, at 1:05 PM, Christopher Done chrisd...@gmail.com

Re: How to fix DatatypeContexts?

2013-07-18 Thread Sjoerd Visscher
What I always do is to write it like this: equal pair@Pair{} = foo pair == bar pair The {} syntax ensures that it doesn't matter how complex the Pair constructor is. Sjoerd On Jul 18, 2013, at 1:52 PM, harry volderm...@hotmail.com wrote: All of the proposed solutions seem to rely on pattern

Re: How to fix DatatypeContexts?

2013-07-18 Thread harry
Sjoerd Visscher-2 wrote equal pair@Pair{} = foo pair == bar pair Interesting solution, I didn't know you could do that. (Do all those who suggested GADTs - you can add a type context to the constructor of a regular data type as well, they don't bring you anything here.) I've also been

RE: How to fix DatatypeContexts?

2013-07-18 Thread p.k.f.holzenspies
I've also been experiencing this a lot in class instances, such as: class Foo f where foo :: a - f a data Bar f a = Foo f = Bar {bar :: f a} instance Foo (Bar f) where foo a = Bar (foo a) Is there any way to avoid repeating the Foo f constraint in the Bar f instance?

Re: How to fix DatatypeContexts?

2013-07-18 Thread Sjoerd Visscher
On Jul 18, 2013, at 2:35 PM, harry volderm...@hotmail.com wrote: Sjoerd Visscher-2 wrote equal pair@Pair{} = foo pair == bar pair Interesting solution, I didn't know you could do that. (Do all those who suggested GADTs - you can add a type context to the constructor of a regular data type

Re: How to fix DatatypeContexts?

2013-07-18 Thread harry
Sjoerd Visscher-2 wrote class Foo f where foo :: a - f a data Bar f a = Foo f = Bar {bar :: f a} instance Foo (Bar f) where foo a = Bar (foo a) No, you can only omit it where you provide Foo f in another way. Which brings me back to my original question - is there any way that

Re: How to fix DatatypeContexts?

2013-07-18 Thread Brandon Allbery
On Thu, Jul 18, 2013 at 9:58 AM, harry volderm...@hotmail.com wrote: Which brings me back to my original question - is there any way that the type system could be enhanced, so that the compiler understands that Bar f = Foo f without being told so explicitly every time? No. The point is,

Re: How to fix DatatypeContexts?

2013-07-18 Thread harry
Brandon Allbery wrote No. The point is, it's not simply a type annotation; it's a *value* (a dictionary) that must be carried along with the rest of the value somehow. The compiler can't always work out statically which instances need to be used with the affected value, so it has to be

Re: Overloaded record fields

2013-07-18 Thread harry
+1 for the -XDotPostfixApply proposal -- View this message in context: http://haskell.1045720.n5.nabble.com/Overloaded-record-fields-tp5731998p5733121.html Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com. ___

Re: How to fix DatatypeContexts?

2013-07-18 Thread Daniel Wagner
On 2013-07-18 10:46, harry wrote: Why not let all types carry the dictionary automatically, or at least every time that it's used, if that would incur a memory/performance penalty? GHC tells me which context to add when it's missing, so it clearly knows. I'm not sure the claim in your second

Re: How to fix DatatypeContexts?

2013-07-18 Thread Edward Kmett
This is exactly what GADTs are for. -Edward On Thu, Jul 18, 2013 at 6:54 AM, harry volderm...@hotmail.com wrote: data Eq a = Pair a = Pair {x::a, y::a} equal :: Pair a - Bool equal pair = (x pair) == (y pair) This code will fail to compile, even with the deprecated DatatypeContexts