Re: overlapping instances in 7.10.1

2015-06-16 Thread Sergei Meshveliani
On Tue, 2015-06-16 at 00:03 +0400, Sergei Meshveliani wrote: [..] 2) At least ghc-7.8.3 and ghc-7.10.1 do the same in this example. May be, you can change this example a bit to make ghc-7.8.3 and ghc-7.10.1 diverse, so that my example bug becomes visible? (they diverse on

RE: overlapping instances in 7.10.1

2015-06-15 Thread Sergei Meshveliani
On Mon, 2015-06-15 at 09:29 +, Simon Peyton Jones wrote: | This is why I think that ghc-7.8.3 treats the OI notion in a more | natural way than ghc-7.10.1 does. | May be, ghc-7.10.1 has a better technical tool for this, but ghc- | 7.8.3 corresponds to a natural notion of OI. |

RE: overlapping instances in 7.10.1

2015-06-15 Thread Sergei Meshveliani
On Mon, 2015-06-15 at 09:29 +, Simon Peyton Jones wrote: | This is why I think that ghc-7.8.3 treats the OI notion in a more | natural way than ghc-7.10.1 does. | May be, ghc-7.10.1 has a better technical tool for this, but ghc- | 7.8.3 corresponds to a natural notion of OI. | |

RE: overlapping instances in 7.10.1

2015-06-14 Thread Sergei Meshveliani
On Sat, 2015-06-13 at 23:07 +, Simon Peyton Jones wrote: (I reformat this text a bit) [..] I finally found time to look into what is happening here. It’s a good illustration of the dangers of overlapping instances. Here is the setup: * Module ResEuc_ * Contains instance

RE: overlapping instances in 7.10.1

2015-06-13 Thread Simon Peyton Jones
Sergei I finally found time to look into what is happening here. It's a good illustration of the dangers of overlapping instances. Here is the setup: * Module ResEuc_ * Contains instance (...)= Ring (ResidueE a) (A) instance (..., Ring

Re: overlapping instances 7.10.1

2015-05-21 Thread adam vogt
Hi Sergei, I think you should use {-# OVERLAPPABLE #-}: see the description here https://ghc.haskell.org/trac/ghc/ticket/9242#comment:16 which is probably in the manual somewhere too. Regards, Adam On Thu, May 21, 2015 at 9:40 AM, Sergei Meshveliani mech...@botik.ru wrote: People, I wrote

Re: overlapping instances in 7.10.1

2015-05-20 Thread Sergei Meshveliani
Now, I delete `OverlappingInstances' from docon.cabal and also from the $doconCpOpt options to call ghc on demotest/Main.hs. And now the test runs correct in ghc-7.10.1 ! Only it is 1.5 times slower than in ghc-7.8.2. So: a) The test intends overlapping instances, b) instance

Re: overlapping instances in 7.10.1

2015-05-20 Thread Sumit Sahrawat, Maths Computing, IIT (BHU)
[Adding ghc-d...@haskell.org to cc] On 21 May 2015 at 02:12, Sergei Meshveliani mech...@botik.ru wrote: Now, I delete `OverlappingInstances' from docon.cabal and also from the $doconCpOpt options to call ghc on demotest/Main.hs. And now the test runs correct in ghc-7.10.1 ! Only

RE: Overlapping Instances + Existentials = Incoherent Instances

2010-02-10 Thread Simon Peyton-Jones
This is a tricky one. The motivating example is this: -- Overlapping instances instance Show a = Show [a] where ... instance Show Char where ... data T where MkT :: Show a = [a] - T f :: T - String f (MkT xs) = show xs ++ \n Here it's clear that the only way to discharge the

Re: Overlapping Instances + Existentials = Incoherent Instances

2010-02-03 Thread Stefan Holdermans
Dan, class C a where foo :: a - String instance C a where foo _ = universal instance C Int where foo _ = Int [...] Now, IncoherentInstances is something most people would suggest you don't use (even people who are cool with OverlappingInstances). However, it turns out that

Re: Overlapping Instances + Existentials = Incoherent Instances

2010-02-03 Thread Dan Doel
On Wednesday 03 February 2010 11:34:27 am Stefan Holdermans wrote: I don't think it's the same thing. The whole point of the existential is that at the creation site of any value of type Ex the type of the value being packaged is hidden. At the use site, therefore, the only suitable instance

Re: Overlapping instances vs. Haskell98 Report [was: How to disable warning for export item 'module ...' exports nothing?]

2008-08-15 Thread Isaac Dupree
Sean Leather wrote: That's interesting. So, maybe there should be some language extension or warning (with associated -fno-warn) for this in GHC. Personally, I prefer the way it's done now. (I guess that's obvious, considering I'm developing a library that will take advantage of it. ;) ) But it

[Haskell-cafe] Re: overlapping instances, selecting if type a does not belong to class?

2007-02-27 Thread Marc Weber
However, it seems that your particular problem can be solved with simpler means: instance (HList a) = HListAppendArbitrary a HNil a where hAppendArbitrary a _ = a instance (HList a, HList b, HList c) = HListAppendArbitrary a (HCons b d) c where hAppendArbitrary a b = hAppend

[Haskell-cafe] Re: overlapping instances, selecting if type a does not belong to class?

2007-02-27 Thread oleg
The problem you report can be fixed with some trickery and local functional dependencies. I'd like to show a different solution, which follows a useful general pattern, of isolating overlapping instances to one small part of the program that analyzes the type. The rest of the type program just

[Haskell-cafe] Re: overlapping instances, selecting if type a does not belong to class?

2007-02-26 Thread Marc Weber
Wow. That said, it is quite possible in Haskell to achieve genuine class-based dispatch, with backtracking if necessary: http://pobox.com/~oleg/ftp/Haskell/poly2.txt Thanks for digging this up. I'll have to reread it tomorrow. I wasn't able to find the definition of AllOf(But): quote

RE: overlapping instances in 6.6 candidate

2006-09-04 Thread Simon Peyton-Jones
You can see the rules here http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions .html#instance-overlap GHC 6.6's story is that an instance declaration can only be overlapped if you compile that module with -fallow-overlapping-instances. Since the list instance for Show was

Re: overlapping instances and constraints

2006-03-11 Thread Claus Reinke
- Haskell would need to be a lot more specific about exactly where context reduction takes place. Consider f xs x = xs == [x] Do we infer the type (Eq a) = [a] - a - Bool? Thereby committing to a particular choice of instance? Or do we (as GHC does) infer the type (Eq [a]) = [a] - a - Bool, so

Re: overlapping instances and constraints

2006-03-08 Thread Claus Reinke
there were a couple of issues Simon raised that I hadn't responded to in my earlier reply. since no-one else has taken them on so far, either, .. - Haskell would need to be a lot more specific about exactly where context reduction takes place. Consider f xs x = xs == [x] Do we infer the type

Re: overlapping instances and constraints

2006-03-01 Thread Ben Rudiak-Gould
Niklas Broberg wrote: Ben Rudiak-Gould wrote: Are there uses of overlapping instances for which this isn't flexible enough? Certainly! Hmm... well, what about at least permitting intra-module overlap in Haskell' (and in GHC without -foverlapping-instances)? It's good enough for many

Re: overlapping instances and constraints

2006-03-01 Thread Ashley Yakeley
Ben Rudiak-Gould wrote: I think all of these problems would go away if overlap was permitted within a module but forbidden across modules. Are there uses of overlapping instances for which this isn't flexible enough? I dislike this on principle. I like the idea that modules can be

Re: overlapping instances and constraints

2006-02-28 Thread Claus Reinke
instance C2 a b | a/=b I was thinking it would be all kinds of useful if we had two predefined classes class Eq a b class NEq a b where Eq has instances exactly when its two types are equal and NEq has instances exactly when its two types are not equal. class Eq a b instance Eq a a

Re: overlapping instances and constraints

2006-02-28 Thread Niklas Broberg
On 2/28/06, Ben Rudiak-Gould [EMAIL PROTECTED] wrote: Simon Peyton-Jones wrote: - A program that type checks can have its meaning changed by adding an instance declaration - Similarly adding import M() can change the meaning of a program (by changing which instances are visible -

Re: overlapping instances and constraints

2006-02-28 Thread Niklas Broberg
Claus Reinke wrote: most of us would be happy if instance contexts would be required to uniquely determine the instance to be chosen, a rather conservative extension of current practice. I'm not so sure about the most of us, as you note yourself the defaulting pattern is quite popular (and

RE: overlapping instances and constraints

2006-02-27 Thread Simon Peyton-Jones
Overlapping instances are undoubtedly useful, but they raise lots of interesting questions. Such as - A program that type checks can have its meaning changed by adding an instance declaration - Similarly adding import M() can change the meaning of a program (by changing which instances are

Re: overlapping instances and constraints

2006-02-27 Thread Claus Reinke
[ I'll only address some of your issues in this message, as they fall nicely under the use of a feature I'd like to see anyway: type disequality constraints ] - A program that type checks can have its meaning changed by adding an instance declaration - Similarly adding import M() can

Re: overlapping instances and constraints

2006-02-27 Thread John Meacham
On Mon, Feb 27, 2006 at 05:09:30PM +0300, Bulat Ziganshin wrote: i had plans to propose the same and even more: instance C2 a b | a/=b I was thinking it would be all kinds of useful if we had two predefined classes class Eq a b class NEq a b where Eq has instances exactly when its two types

Re: overlapping instances in ghc-6.5

2006-02-06 Thread Christian Maeder
The attached 4 files compile with ghc-6.4.1 and fail with ghc-6.5.20060201 (see below). Also, if I delete the Int and Integer instances in Common/ATerm/Conversion.hs the error remains the same for ghc-6.5 whereas ghc-6.4.1 correctly complains about No instance for (ShATermConvertible Int)

RE: overlapping instances in ghc-6.5

2006-02-06 Thread Simon Peyton-Jones
| To: Simon Peyton-Jones | Cc: glasgow-haskell-bugs@haskell.org | Subject: Re: overlapping instances in ghc-6.5 | | The attached 4 files compile with ghc-6.4.1 and fail with | ghc-6.5.20060201 (see below). | | Also, if I delete the Int and Integer instances in | Common/ATerm/Conversion.hs the error

[Haskell-cafe] Re: Overlapping instances

2005-08-24 Thread Ashley Yakeley
In article [EMAIL PROTECTED], Frank [EMAIL PROTECTED] wrote: I would like to state that a class Sup is exhaustively broken down in two subclasses Sub1 and Sub2 (meaning, for every instance of Sub1 and every instance of Sub2, the methods in Sup apply). I try to code this as: instance

RE: Overlapping instances and multi-parameter classes

2004-03-11 Thread Simon Peyton-Jones
I had a look. It turns out to be an utterly bogus and incorrect test for overlap in 6.2. As it happens, I've already re-written that part of the compiler in the HEAD, to do lazy overlap resolution. In GHC 6.2 the instances instance C a Bool instance C Bool a are rejected because

RE: overlapping instances and modules

2004-02-12 Thread Simon Peyton-Jones
I believe this is a buglet in the error message itself. If you compile one file at a time, you instead get: Overlapping instance declarations: In module Test: C (T m) In module Test: C (t m) The complaint here is reasonable: you need -fallow-overlapping-instances when compiling Test. (One

RE: overlapping instances

2003-10-20 Thread Simon Peyton-Jones
First thing to say is that I'm changing the way in which overlapping instance errors are reported. At the moment (ghc 6.0, 6.2) you get an overlap error if there *might* be an overlap problem. For example: overlap.hs:23: Overlapping instance declarations: overlap.hs:23: Convertable a

Re: overlapping instances

2003-10-15 Thread Arie Peterson
What would have GHC do for the convert :: String - String case? (You'd like convert = id here but it's not clear to me what the general rule should be.) mike The general rule should be that convert :: a - a = id, no matter what other instances are available. Is there any way to tell GHC

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 why.

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

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 hugs

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

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

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

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

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 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 'x' is the

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 - Value | test

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 avoid

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

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 uses Eq

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 x == y =

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] - [Bool] g h

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 String)

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 can

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 that the type

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 Mercury,

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) is not

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 should be.

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

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 is

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 to

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 `f',

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 problems

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

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

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 Haskell, all

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 way it

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-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 consistently,

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. http://research.microsoft.com/users/simonpj/Papers/multi.ps.gz

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 not

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, in a sense

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 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 says: Thanks but why

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)) given

Re: overlapping instances

1998-06-04 Thread Sigbjorn Finne
S.D.Mechveliani writes: Dear ghc developers, Could you, please, tell me 1. What are the ghc plans concerning the overlapping instances ? For it looks like ghc-3.02 does not support them. It does, but the 3.02 driver doesn't `re-export' the command-line option expected by the