How to fix DatatypeContexts?

2013-07-18 Thread harry
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
extension, because equal must be given the Eq a => constraint, even though
this has already been declared on the Pair type.

Some of my code is littered with such redundant type constraints (although
some of them could be replaced with a redundant pattern match). A proposal
to enhance DatatypeContexts (#8026) in this way was rejected as unsound, as
some nefarious uses of undefined would break the type system.

Is there any way that the type system could be enhanced to avoid this
redundancy?



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.

___
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
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  wrote:

> 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 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  wrote:

> 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  wrote:
> 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


___
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
Good point, classic use-case for GADTs.


On 18 July 2013 13:11, Sjoerd Visscher  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  wrote:
>
> > 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  wrote:
> > 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
>
>
___
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 harry
All of the proposed solutions seem to rely on pattern matching in the
constructor, which isn't always feasible. Here's a slightly better example:

data Pair a = (Num a, Eq a) => Pair {x::a,y::a}

equal :: Pair a -> Bool
equal pair = (foo pair) == (bar pair)

foo pair = (x pair) * (y pair)

bar pair = (y pair) + (x pair)

Now imagine that foo and bar are part of a library which I don't control, or
that for some other reason I can't just change foo and bar to take only the
components of Pair (e.g. it's a complex type with numerous components and
subcomponents).



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103p5733110.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.

___
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 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  wrote:

> All of the proposed solutions seem to rely on pattern matching in the
> constructor, which isn't always feasible. Here's a slightly better example:
> 
> data Pair a = (Num a, Eq a) => Pair {x::a,y::a}
> 
> equal :: Pair a -> Bool
> equal pair = (foo pair) == (bar pair)
> 
> foo pair = (x pair) * (y pair)
> 
> bar pair = (y pair) + (x pair)
> 
> Now imagine that foo and bar are part of a library which I don't control, or
> that for some other reason I can't just change foo and bar to take only the
> components of Pair (e.g. it's a complex type with numerous components and
> subcomponents).
> 
> 
> 
> --
> View this message in context: 
> http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103p5733110.html
> Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
> Nabble.com.
> 
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
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 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 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?



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103p5733112.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.

___
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 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?



Dear Harry, et al,

The problem here is that GADT-constructors simply "carry" the appropriate 
dictionaries. When you *produce* an element of a GADT where the constructor 
requires a dictionary, you must provide it there. In this case, for a variable 
f, you don't have a dictionary, so you could read the constraint and instance 
head as "if you give me a Foo-dictionary for f, then I will wrap it in a Bar."

Another way of looking at it is that the type "Bar f" only 'exists' for 'f's 
that are 'Foo's. If you don't know whether a particular 'f' is a 'Foo', you 
don't know whether Bar f exists.

In short, I think that there is no such way.

Regards,
Philip

___
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 Sjoerd Visscher

On Jul 18, 2013, at 2:35 PM, harry  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 as well, they don't bring you anything here.)

What it brings in my opinion is clarity, but that's subjective of course.

> 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?

No, you can only omit it where you provide Foo f in another way. With equal you 
provide it with the Pair value. But here you're constructing a value, so you'll 
have to provide the Foo f. If all the methods in the class receive a value, 
then you can omit it, f.e.:

class Baz f where
  baz :: f a -> a

data Bar f a = Baz f => Bar {bar :: f a}

instance Baz (Bar f) where
  baz (Bar fa) = baz fa

--
Sjoerd
  
___
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 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 the
type system could be enhanced, so that the compiler "understands" that Bar f
=> Foo f without being told so explicitly every time?



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103p5733117.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.

___
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 Brandon Allbery
On Thu, Jul 18, 2013 at 9:58 AM, harry  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, 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 available at run time; the
context is effectively declaring that the run-time dictionary is a required
extra parameter. And it wouldn't really be workable for some types to
secretly imply that extra parameter and others not.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
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 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 available at run time; the
> context is effectively declaring that the run-time dictionary is a
> required
> extra parameter. And it wouldn't really be workable for some types to
> secretly imply that extra parameter and others not.

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.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103p5733119.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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.

___
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 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 sentence is true. For example,

foo :: a -> a -> Bool
foo = (==)

bar :: a -> a -> Bool
bar = foo

GHC (rightly) complains about foo, but makes no complaint about bar. 
That is, if a thing only works in the presence of a constraint, you need 
to have that constraint visible in the type, every time, or else 
downstream dependencies can reasonably make wrong assumptions.


~d

___
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 Edward Kmett
This is exactly what GADTs are for.

-Edward

On Thu, Jul 18, 2013 at 6:54 AM, harry  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
> extension, because equal must be given the Eq a => constraint, even though
> this has already been declared on the Pair type.
>
> Some of my code is littered with such redundant type constraints (although
> some of them could be replaced with a redundant pattern match). A proposal
> to enhance DatatypeContexts (#8026) in this way was rejected as unsound, as
> some nefarious uses of undefined would break the type system.
>
> Is there any way that the type system could be enhanced to avoid this
> redundancy?
>
>
>
> --
> View this message in context:
> http://haskell.1045720.n5.nabble.com/How-to-fix-DatatypeContexts-tp5733103.html
> Sent from the Haskell - Glasgow-haskell-users mailing list archive at
> Nabble.com.
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users