RE: overlapping instances and functional dependencies

2003-08-21 Thread Simon Peyton-Jones
| With overlapping instances, I'm allowed | | class OK x y | | instance Functor f => OK (f x) (f y) | | instance Functor f => OK x (f y) | | but I'm not allowed | | class Bad x y z | x y -> z | | instance Functor f => Bad (f x) (f y) Bool | | instance Functor f => Bad x (f y) Int

RE: overlapping instances and functional dependencies

2003-08-21 Thread Simon Peyton-Jones
| class C a b c | a b -> c where | f :: a -> b -> c | | instance C a b c => C a (x,y,b) c where | f a (_,_,b) = f a b | | instance C a (a,c,b) c where | f _ (_,c,_) = c | ghci -fglasgow-exts -fallow-overlapping-instances compiles it without | complaint but hug

Re: overlapping instances and functional dependencies

2003-08-21 Thread Tom Pledger
C T McBride writes: : | but I'm not allowed | | class Bad x y z | x y -> z | | instance Functor f => Bad (f x) (f y) Bool | | instance Functor f => Bad x (f y) Int | | I don't quite see why. Naively, I imagine that if the OK instances are | effectively prioritized, then Bad's r

Re: overlapping instances and functional dependencies

2003-08-21 Thread C T McBride
Hi all With overlapping instances, I'm allowed class OK x y instance Functor f => OK (f x) (f y) instance Functor f => OK x (f y) but I'm not allowed class Bad x y z | x y -> z instance Functor f => Bad (f x) (f y) Bool instance Functor f => Bad x (f y) Int I don't quite see wh

Re: overlapping instances and functional dependencies

2003-08-20 Thread oleg
Wolfgang Jeltsch has observed: > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c > > instance C a b c => C a (x,y,b) c where > f a (_,_,b) = f a b > > instance C a (a,c,b) c where > f _ (_,c,_) = c > ghci -fglasgow-exts -fallow-overlapping-

Re: overlapping instances and functional dependencies

2003-08-19 Thread Wolfgang Jeltsch
Hello, I think, I realized now what my mistake was. The handling of overlapping instances comes into play when the compiler has to decide which method definition to choose for a specific instance. It is not for choosing one of more possible instances. In my example, C Int (Int,Char,Bool) Int a

Re: overlapping instances and functional dependencies

2003-08-17 Thread Wolfgang Jeltsch
I wrote on Saturday, 2003-08-09, 01:32, CEST: > Hello, > > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c > > instance C a b c => C a (x,y,b) c where > f a (_,_,b) = f a b > > instance C a (a,c,b) c where > f _ (_,c,_) = c > ghci -fglasgow-

RE: overlapping instances and functional dependencies

2003-08-14 Thread Hal Daume
Suppose somewhere we have an instance: instance C Int Bool Int when the first instance decl you have says we also have instance C Int (x,y,Bool) Int in this case, Int + (x,y,Bool) should uniq. specify Int. however, we also have: instance C a (a,c,b) c where, if we let a=Int, b=Bool, c=C

Re: overlapping instances and functional dependencies

2003-08-14 Thread Andrew J Bromage
G'day all. On Sat, Aug 09, 2003 at 01:32:49AM +0200, Wolfgang Jeltsch wrote: > ghci -fglasgow-exts -fallow-overlapping-instances compiles it without > complaint If it helps, ghci will complain the first time you actually try to use it. Cheers, Andrew Bromage ___

Re: Overlapping instances in existentials

2003-06-20 Thread oleg
Ed Komp replied to Simon Peyton-Jones: > Within the GHC compiler > > can't be instantiated to Double --- but that's tricky to pin down. > this may be tricky to pin down. > But, there is specific information in my example to exclude Double: > I had carefully constructed the type definitions to avo

Re: Overlapping instances in existentials

2003-06-20 Thread Dean Herington
Dylan Thurston wrote: > On Thu, Jun 19, 2003 at 11:08:35AM -0500, Ed Komp wrote: > > > | type BaseType = Either Integer ( Either Bool () ) > > > | > > > | type Value = (Either Double BaseType) > > > | > > > | data Foo = forall x. (SubType x BaseType) => MkFoo x > > > | > > > | test :: Foo

Re: Overlapping instances in existentials

2003-06-20 Thread Dylan Thurston
On Thu, Jun 19, 2003 at 11:08:35AM -0500, Ed Komp wrote: > > | type BaseType = Either Integer ( Either Bool () ) > > | > > | type Value = (Either Double BaseType) > > | > > | data Foo = forall x. (SubType x BaseType) => MkFoo x > > | > > | test :: Foo -> Value > > | test (MkFoo x) = inj x

Re: Overlapping instances in existentials

2003-06-20 Thread Ed Komp
Simon, Thanks for the extended response to my question about overlapping instances. Before my original posting, I had read a posting that included the example with Show that you included in your response. I believed (and still do) that my specific case is a bit different. | To determine (SubType

Re: Overlapping instances

2000-03-08 Thread Fergus Henderson
On 08-Mar-2000, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote: > There has been a great deal of mail about overlapping > instances. I confess that I have read little of it. > But I am interested in it. > > Would someone like to write a summary of > what the issues are >

Re: overlapping instances(this 15k posting)

2000-03-07 Thread Michal Gajda
Please, organize your long postings in chapters to provide easier reading and reference. IMHO bigger writings need to be structured. Best regards and thx in advance Michal Gajda [EMAIL PROTECTED] PS To be honest, I dreamed of abstracts at the beginning of each letter :)

Re: overlapping instances

2000-02-29 Thread Marcin 'Qrczak' Kowalczyk
Tue, 29 Feb 2000 14:20:32 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > > h :: Eq a => a -> a -> Int > > h x y = if x == y then 0 else 1 + h [x] [y] > > which would make h "1" "2" return 7 if in some other module there is: > > instance Eq [[[String]]] where > >

Re: overlapping instances

2000-02-29 Thread Marcin 'Qrczak' Kowalczyk
On Mon, 28 Feb 2000, S.D.Mechveliani wrote: > If we want the recent implementations to compile this as needed, we > have to write > g :: (Eq a, Eq (Maybe a)) => (a -> Bool) -> [a] -> [Bool] > > g h xs@(x:_) = (Just x == Just x) : map h xs > > - "because this g us

Re: overlapping instances

2000-02-27 Thread Marcin 'Qrczak' Kowalczyk
Sun, 27 Feb 2000 19:21:05 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > module G (g) > where > g:: Eq a => (a -> Bool) -> [a] -> [Bool] > gh xs = map h xs Back to the topic of visible imports. Change this definition to: g:: Eq a => (a -> Bool) -> [a] -> [B

Re: overlapping instances

2000-02-24 Thread Fergus Henderson
On 24-Feb-2000, Jeffrey R. Lewis <[EMAIL PROTECTED]> wrote: > The example with polymorphic recursion is a nice example. [...] > Especially given the above example, I don't think that trying to make overlapping >behave > consistently, regardless of instance scope, is the right approach. For Mercu

Re: overlapping instances

2000-02-24 Thread Fergus Henderson
On 24-Feb-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Thu, 24 Feb 2000 14:17:43 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > > > Seeing `Just x1 == Just x2' > > the compiler extends *silently* the context for f: > > It would mean tha

Re: overlapping instances

2000-02-24 Thread Jeffrey R. Lewis
Marcin 'Qrczak' Kowalczyk wrote: > The other issue is efficiency if you want f to behave the same way even > when the instance Eq (Maybe String) is not visible at f's definition. > It would mean that every overloaded function must be extended to > directly receive all dictionaries it needs. This

Re: overlapping instances

2000-02-24 Thread Jeffrey R. Lewis
"S.D.Mechveliani" wrote: > > The philosophy should be: > -- > seeing in the program f ["foo","bar","baz"] > the compiler judges that f applies to certain xs :: [String]. > According to the compiled type of f, > the instances Eq String, Eq (Maybe Strin

Re: overlapping instances

2000-02-24 Thread Jeffrey R. Lewis
"S.D.Mechveliani" wrote: > > That is, f receives a dictionary of Eq methods on the type a, as > > specified in its type. It builds a dictionary of Eq methods on the > > type Maybe a itself, but the fact that it uses instance Eq (Maybe a) > > is not visible outside. > > No. Probably, here how it s

Re: overlapping instances

2000-02-24 Thread Marcin 'Qrczak' Kowalczyk
Thu, 24 Feb 2000 14:17:43 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > > That is, f receives a dictionary of Eq methods on the type a, as > > specified in its type. It builds a dictionary of Eq methods on the > > type Maybe a itself, but the fact that it uses instance Eq (Maybe a) >

Re: overlapping instances: And a question about newtypes

2000-02-20 Thread Fergus Henderson
On 21-Feb-2000, Brian Boutel <[EMAIL PROTECTED]> wrote: > On Sunday, February 20, 2000 4:13 PM, Fergus Henderson > > > > Well, you can always defined a type using Tree which _is_ an instance of > > Ord: > > > > newtype OrdTree = MkOrdTree Tree > > instance Ord OrdTree where ... > > > > S

RE: overlapping instances: And a question about newtypes

2000-02-20 Thread Brian Boutel
On Sunday, February 20, 2000 4:13 PM, Fergus Henderson [SMTP:[EMAIL PROTECTED]] wrote: > > Well, you can always defined a type using Tree which _is_ an instance of Ord: > > newtype OrdTree = MkOrdTree Tree > instance Ord OrdTree where ... > > So I don't see this as a disaster. > The

Re: overlapping instances

2000-02-19 Thread Fergus Henderson
On 20-Feb-2000, Brian Boutel <[EMAIL PROTECTED]> wrote: > > Obviously, in general, information hiding is useful. Here, the specific > question is about instance declarations.Is there any value in being able to > hide them? > > I think the answer is no, for the following reasons: > > 1) There

RE: overlapping instances

2000-02-19 Thread Brian Boutel
On Friday, February 18, 2000 7:17 PM, Fergus Henderson [SMTP:[EMAIL PROTECTED]] wrote: > It's just a question of information hiding. > It lets you declare a type to be an instance of a public type class > without exporting that fact (and hence exporting those methods). > > > In Haskell, you can h

Re: overlapping instances

2000-02-17 Thread Fergus Henderson
On 18-Feb-2000, Brian Boutel <[EMAIL PROTECTED]> wrote: > > OK, I understand now. But what advantage does explicit control of instance > import/export give you over the current Haskell rule? It's just a question of information hiding. It lets you declare a type to be an instance of a public ty

RE: overlapping instances

2000-02-17 Thread Brian Boutel
On Friday, February 18, 2000 1:46 AM, Fergus Henderson [SMTP:[EMAIL PROTECTED]] wrote: > > Mercury allows private instances, but it does not allow shadowing. > For any given class and type, there can only be one instance; > that instance can be public, or private, but not both. > > If you allow s

Re: overlapping instances

2000-02-17 Thread Fergus Henderson
On 17-Feb-2000, Brian Boutel <[EMAIL PROTECTED]> wrote: > On Thursday, February 17, 2000 7:02 PM, Fergus Henderson > > Well, I remain unconvinced. In Mercury, we give the user control > > over whether instance declarations are exported or not, and it > > works quite nicely, IMHO. I think the pr

Re: overlapping instances

2000-02-17 Thread Jeffrey R. Lewis
Fergus Henderson wrote: > On 16-Feb-2000, Jeffrey R. Lewis <[EMAIL PROTECTED]> wrote: > > To my mind, the biggest flaw with overlapping instances is the separate > > compilation issue: to whit, if the `instance Eq (Maybe String)' was in > > a different module, not imported by the module defining

RE: overlapping instances

2000-02-17 Thread Brian Boutel
On Thursday, February 17, 2000 7:02 PM, Fergus Henderson [SMTP:[EMAIL PROTECTED]] wrote: >> > Well, I remain unconvinced. In Mercury, we give the user control > over whether instance declarations are exported or not, and it > works quite nicely, IMHO. I think the problems that you are referring

Re: overlapping instances

2000-02-16 Thread Fergus Henderson
On 17-Feb-2000, Brian Boutel <[EMAIL PROTECTED]> wrote: > On Thursday, February 17, 2000 3:03 PM, Fergus Henderson > [SMTP:[EMAIL PROTECTED]] wrote: > >> > > If Haskell had explicit imports and exports of instance declarations, > > then I could perhaps buy this argument. But it doesn't. In Hask

RE: overlapping instances

2000-02-16 Thread Brian Boutel
On Thursday, February 17, 2000 3:03 PM, Fergus Henderson [SMTP:[EMAIL PROTECTED]] wrote: >> > If Haskell had explicit imports and exports of instance declarations, > then I could perhaps buy this argument. But it doesn't. In Haskell, > all instance declarations defined in a module are always ex

Re: overlapping instances

2000-02-16 Thread Fergus Henderson
On 16-Feb-2000, Jeffrey R. Lewis <[EMAIL PROTECTED]> wrote: > To my mind, the biggest flaw with overlapping instances is the separate > compilation issue: to whit, if the `instance Eq (Maybe String)' was in > a different module, not imported by the module defining `f', then > Marcin's definition o

Re: overlapping instances

2000-02-16 Thread Jeffrey R. Lewis
Marcin 'Qrczak' Kowalczyk wrote: > Wed, 16 Feb 2000 15:45:07 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > > > I fear, I am loosing the thread. The discussion was on the > > overlapping instances. And this latter question is maybe, on giving > > a polymorphic function to another funct

Re: overlapping instances

2000-02-16 Thread Carl R. Witty
[EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) writes: > I do not blame ghc for that. IMHO overlapping instances together > with the rest of Haskell are impossible to be safely and effectively > implemented. > > Unless one accepts that subtle differences in contexts, ones > depending on the implem

Re: overlapping instances

2000-02-16 Thread Marcin 'Qrczak' Kowalczyk
Wed, 16 Feb 2000 15:45:07 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > I fear, I am loosing the thread. The discussion was on the > overlapping instances. And this latter question is maybe, on giving > a polymorphic function to another function as the argument. I am > not an implemen

Re: overlapping instances

2000-02-15 Thread Marcin 'Qrczak' Kowalczyk
Tue, 15 Feb 2000 17:51:51 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > Here A is a superclass for B, so, `B a =>' is a more special > condition than `A a =>'. I am not brave enough to try to formulate general rules of determining which context is more general,

Re: overlapping instances

2000-02-15 Thread Jeffrey R. Lewis
Tom Pledger wrote: > Marcin 'Qrczak' Kowalczyk writes: > > [...] However in the following case there is an ambiguity that I > > don't know how to resolve - overlapping instances don't solve what > > they seemed to claim to solve: > > > > classA a where ... > > class A a => B a where

Re: overlapping instances

2000-02-14 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: > [...] However in the following case there is an ambiguity that I > don't know how to resolve - overlapping instances don't solve what > they seemed to claim to solve: > > classA a where ... > class A a => B a where ... > classC a where ..

Re: overlapping instances

2000-02-14 Thread Marcin 'Qrczak' Kowalczyk
Thu, 10 Feb 2000 23:00:08 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > > Generally it does not fit into my mental model of a Haskell class. > > How could it be that adding an instance *constrains* what else we > > can do with a type (define an instance of another class)? > > In what

Re: overlapping instances

2000-02-08 Thread Jeffrey R. Lewis
"Carl R. Witty" wrote: > "Jeffrey R. Lewis" <[EMAIL PROTECTED]> writes: > > > Marcin 'Qrczak' Kowalczyk wrote: > > > Parts of context reduction must be deferred, contexts must be left > > > more complex, which as I understand leads to worse code - only to > > > make overlapping instances behave c

Re: overlapping instances

2000-02-07 Thread Carl R. Witty
"Jeffrey R. Lewis" <[EMAIL PROTECTED]> writes: > Marcin 'Qrczak' Kowalczyk wrote: > > Parts of context reduction must be deferred, contexts must be left > > more complex, which as I understand leads to worse code - only to > > make overlapping instances behave consistently, even where they are >

Re: overlapping instances

2000-02-07 Thread Jeffrey R. Lewis
Marcin 'Qrczak' Kowalczyk wrote: > Sun, 06 Feb 2000 23:21:38 -0800, Jeffrey R. Lewis <[EMAIL PROTECTED]> pisze: > > > If context reduction choses a more generic instance when a more > > specific one exists, then I consider that a bug. > >

Re: overlapping instances

2000-02-07 Thread Marcin 'Qrczak' Kowalczyk
Sun, 06 Feb 2000 23:21:38 -0800, Jeffrey R. Lewis <[EMAIL PROTECTED]> pisze: > If context reduction choses a more generic instance when a more > specific one exists, then I consider that a bug. Section 4.4 Parts of context reducti

Re: overlapping instances

2000-02-06 Thread Jeffrey R. Lewis
Marcin 'Qrczak' Kowalczyk wrote: > Requires overlapping instances in a case where in fact something is > X and the way it should be Z is different than that induced by X. > And overlapping instances themselves can be lost because of context > reduction, where a polymorphic function will use the g

Re: overlapping instances

2000-02-06 Thread Marcin 'Qrczak' Kowalczyk
Sun, 6 Feb 2000 20:33:52 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > It is clear from the example of my previous letter that some > operation may be computed in different ways in general and in > several special situations. This leads to overlapping instances. This does not *requir

Re: Overlapping instances?

1999-06-14 Thread Lars Henrik Mathiesen
> Date: Sun, 13 Jun 1999 16:46:57 -0400 > From: Kevin Atkinson <[EMAIL PROTECTED]> > Thanks but why is this OK? Sorry, I misunderstood the question. > class T f r > > instance T a (a) > instance T (c a b) (c a (b)) > I mean the comman instance here is T (c a b) (c a (b)). Well, i

RE: Overlapping instances?

1999-06-14 Thread Mark P Jones
Let me define some terms. If pi and pi' are two class constraints, then we say that pi and pi' are overlapping if S(pi) = S'(pi') for some substitutions S and S'. Thus C Int and C [a] do not overlap, but C (a,Int) and C (Bool, a) do overlap. As it says in the Hugs manual, overlapping instances

Re: Overlapping instances?

1999-06-13 Thread Lars Henrik Mathiesen
> Date: Sun, 13 Jun 1999 01:51:06 -0400 > From: Kevin Atkinson <[EMAIL PROTECTED]> > Could some one explain to me why [this is not OK]: > class T f r > > instance T a (d a) > instance T (c a b) (c a (d b)) Because, just as Hugs says: > *** Common instance : T (a b c) (a b (a b c

Re: Overlapping instances?

1999-06-13 Thread Kevin Atkinson
Lars Henrik Mathiesen wrote: > > > Date: Sun, 13 Jun 1999 01:51:06 -0400 > > From: Kevin Atkinson <[EMAIL PROTECTED]> > > > Could some one explain to me why [this is not OK]: > > > class T f r > > > > instance T a (d a) > > instance T (c a b) (c a (d b)) > > Because, just as Hugs s