Re: flexible contexts and context reduction

2008-03-27 Thread Tom Schrijvers
On Wed, 26 Mar 2008, Ganesh Sittampalam wrote: On Wed, 26 Mar 2008, Ross Paterson wrote: On Wed, Mar 26, 2008 at 08:52:43PM +, Ganesh Sittampalam wrote: I'm a bit confused about why the following program doesn't compile (in any of 6.6.1, 6.8.1 and 6.9.20080316). Shouldn't the Ord (a, b)

RE: flexible contexts and context reduction

2008-03-27 Thread Simon Peyton-Jones
| To use bar, you need (Ord a, Ord b). You're assuming that Ord (a, b) | implies that, but it's the other way round. | | Logically, the implication holds. There's an equivalence: | | Ord a /\ Ord b = Ord (a,b) | ... | The problem with dictionaries is that you have to store the

RE: flexible contexts and context reduction

2008-03-27 Thread Tom Schrijvers
You're talking about something else: the dictionaries (Ord a, Ord b) from which the Ord (a,b) dictionary were constructed. We don't have a very good name for these guys, but superclass isn't a good one. Otherwise I agree with all you say. Your idea of using type families is cool. |

RE: flexible contexts and context reduction

2008-03-27 Thread Simon Peyton-Jones
Why unfortunately? Looks fine to me. Simon | | Unfortunately, GHC accepts the following: | | {-# LANGUAGE FlexibleInstances #-} | module Foo2 where | | data Foo = Foo | deriving Eq | | instance Ord (Foo, Foo) where | (Foo, Foo) (Foo, Foo) = False

RE: flexible contexts and context reduction

2008-03-27 Thread Sittampalam, Ganesh
@haskell.org; Martin Sulzmann Subject: RE: flexible contexts and context reduction Why unfortunately? Looks fine to me. Simon | | Unfortunately, GHC accepts the following: | | {-# LANGUAGE FlexibleInstances #-} | module Foo2 where | | data Foo = Foo | deriving Eq | | instance Ord (Foo, Foo) where

RE: flexible contexts and context reduction

2008-03-27 Thread Simon Peyton-Jones
@haskell.org; Martin Sulzmann | Subject: RE: flexible contexts and context reduction | | Why unfortunately? Looks fine to me. | | Simon | | | | | Unfortunately, GHC accepts the following: | | | | {-# LANGUAGE FlexibleInstances #-} | | module Foo2 where | | | | data Foo = Foo | | deriving Eq

RE: flexible contexts and context reduction

2008-03-27 Thread Tom Schrijvers
@haskell.org; Martin Sulzmann Subject: RE: flexible contexts and context reduction Why unfortunately? Looks fine to me. Simon | | Unfortunately, GHC accepts the following: | | {-# LANGUAGE FlexibleInstances #-} | module Foo2 where | | data Foo = Foo | deriving Eq | | instance Ord (Foo, Foo) where

RE: flexible contexts and context reduction

2008-03-27 Thread Sittampalam, Ganesh
If you write the instance instance Theta = Foo (T a b) where ... where Theta is an arbitrary context, then, given a dictionary for (Foo (T a b)), you can get dictionaries for each constraint in Theta. Or in logic Theta = Foo (T a b) In your example, Theta is empty. If

RE: flexible contexts and context reduction

2008-03-27 Thread Sittampalam, Ganesh
Tom Schrijvers wrote: On Wed, 26 Mar 2008, Ganesh Sittampalam wrote: On Wed, 26 Mar 2008, Ross Paterson wrote: On Wed, Mar 26, 2008 at 08:52:43PM +, Ganesh Sittampalam wrote: I'm a bit confused about why the following program doesn't compile (in any of 6.6.1, 6.8.1 and 6.9.20080316).

Re: flexible contexts and context reduction

2008-03-27 Thread Claus Reinke
perhaps i'm missing something but, instead of trying to deduce conditions from conclusions, why can't you just follow ghc's suggestion, and add the constraints to the constructor? data Foo a where Foo1 :: a - Foo a Foo2 :: (Ord a,Ord b) = Foo a - Foo b - Foo (a, b) (possibly with another

RE: flexible contexts and context reduction

2008-03-27 Thread Sittampalam, Ganesh
: glasgow-haskell-users@haskell.org Subject: Re: flexible contexts and context reduction perhaps i'm missing something but, instead of trying to deduce conditions from conclusions, why can't you just follow ghc's suggestion, and add the constraints to the constructor? data Foo a where Foo1

Re: flexible contexts and context reduction

2008-03-27 Thread Claus Reinke
Because I want to be able to make Foo values where the parameter type isn't in Ord, too. I just want unFoo to work on specific Foo values where it is. but your recursive function requires a recursive constraint, which your data type does not guarantee by construction, and which the Ord

RE: flexible contexts and context reduction

2008-03-27 Thread Sittampalam, Ganesh
Because I want to be able to make Foo values where the parameter type isn't in Ord, too. I just want unFoo to work on specific Foo values where it is. but your recursive function requires a recursive constraint, which your data type does not guarantee byconstruction, and which the

Re: flexible contexts and context reduction

2008-03-27 Thread Tristan Allwood
to work on specific Foo values where it is. -Original Message- From: Claus Reinke [mailto:[EMAIL PROTECTED] Sent: 27 March 2008 12:25 To: Sittampalam, Ganesh; Ganesh Sittampalam Cc: glasgow-haskell-users@haskell.org Subject: Re: flexible contexts and context reduction perhaps i'm

Re: flexible contexts and context reduction

2008-03-26 Thread Ross Paterson
On Wed, Mar 26, 2008 at 08:52:43PM +, Ganesh Sittampalam wrote: I'm a bit confused about why the following program doesn't compile (in any of 6.6.1, 6.8.1 and 6.9.20080316). Shouldn't the Ord (a, b) context be reduced? {-# LANGUAGE FlexibleContexts #-} module Test2 where foo :: Ord

Re: flexible contexts and context reduction

2008-03-26 Thread Ganesh Sittampalam
On Wed, 26 Mar 2008, Ross Paterson wrote: On Wed, Mar 26, 2008 at 08:52:43PM +, Ganesh Sittampalam wrote: I'm a bit confused about why the following program doesn't compile (in any of 6.6.1, 6.8.1 and 6.9.20080316). Shouldn't the Ord (a, b) context be reduced? To use bar, you need (Ord