Re: [Haskell] A problem with overlapping instances and super-classes

2008-06-10 Thread Claus Reinke
Yes indeed, this is one of those "well-known" (ie not at all well known, but folk lore) problems with overlapping instances, at least in programs where different instances can be in scope at different times. I think these examples are subtly different (eg, some trip up Hugs as well,

Re: [Haskell] A problem with overlapping instances and super-classes

2008-06-10 Thread Ian Lynagh
On Mon, Jun 09, 2008 at 09:21:02AM +0100, Simon Peyton-Jones wrote: > > This isn't great, but it's not really different than is the case for > non-overlapping instances. Suppose module B1 declares 'instance C T', > and uses that instance; and module B2 declar

Re: [Haskell] A problem with overlapping instances and super-classes

2008-06-09 Thread Claus Reinke
This isn't great, but it's not really different than is the case for non-overlapping instances. Suppose module B1 declares 'instance C T', and uses that instance; and module B2 declares a *different* 'instance C T', and uses that instance; and Main imports B1 a

RE: [Haskell] A problem with overlapping instances and super-classes

2008-06-09 Thread Simon Peyton-Jones
Yes indeed, this is one of those "well-known" (ie not at all well known, but folk lore) problems with overlapping instances, at least in programs where different instances can be in scope at different times. It's discussed (not very clearly) in http://www.haskell.org/ghc/d

[Haskell] A problem with overlapping instances and super-classes

2008-06-07 Thread Iavor Diatchki
Hello, (you should be able to copy and paste the code in this email into two modules called A and B to try it out) > {-# LANGUAGE OverlappingInstances #-} > module A where This module, together with module 'B', illustrates a problem in some implementations of overlapping ins

RE: [Haskell] [Fwd: undecidable & overlapping instances: a bug?]

2007-10-17 Thread Simon Peyton-Jones
ED] | Sent: 17 October 2007 19:19 | To: Mark P Jones | Cc: Simon Peyton-Jones; Haskell users; Tom Schrijvers; Martin Sulzmann | Subject: Re: [Haskell] [Fwd: undecidable & overlapping instances: a bug?] | | Hi, | Mark is quite right, and there is a bug report that documents the p

Re: [Haskell] [Fwd: undecidable & overlapping instances: a bug?]

2007-10-17 Thread Iavor Diatchki
Hi, Mark is quite right, and there is a bug report that documents the problem: http://hackage.haskell.org/trac/ghc/ticket/1241 The trac ticket is targeting GHC 6.8 but the ticket is still open. I have not had a chance to try out any of the 6.8 release candidates yet, so I am not sure if there have

Re: [Haskell] [Fwd: undecidable & overlapping instances: a bug?]

2007-10-17 Thread Mark P Jones
Simon Peyton-Jones wrote: | I am quite intrigued at the behaviour examplified in the attached module. | It's true I am a newbie and probably don't quite get the whole consequence | spectrum of -fallow-undecidable-instances, but why providing that dummy | instance (commented out) get the thing to

RE: [Haskell] [Fwd: undecidable & overlapping instances: a bug?]

2007-10-17 Thread Simon Peyton-Jones
| I am quite intrigued at the behaviour examplified in the attached module. | It's true I am a newbie and probably don't quite get the whole consequence | spectrum of -fallow-undecidable-instances, but why providing that dummy | instance (commented out) get the thing to compile? Sorry I must have

[Haskell] [Fwd: undecidable & overlapping instances: a bug?]

2007-10-16 Thread Jorge Marques Pelizzoni
m Original Assunto: undecidable & overlapping instances: a bug? De: "Jorge Marques Pelizzoni" <[EMAIL PROTECTED]> Data:Sab, Outubro 13, 2007 5:59 am Para:"GHC users" <[EMAIL PROTECTED]> ---

overlapping instances and modules

2004-01-13 Thread Iavor S. Diatchki
hello, i am a bit stuck on the following problem, which seems to be GHC related. consider the following two modules: > {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-} > module Test where > > data T m a = T (m a) > > class C m where get :: m a > > instance C (

Re: GHC allow-overlapping-instances (PART II)

2003-10-03 Thread Wolfgang Jeltsch
> GHC allows this with -fallow-overlapping-instances flag on, but why? Is [1] > more specific than [2] or the other way round? RTFM, i.e., the GHC User's Guide. Which instance is considered more special depends only on what comes after the class identifier, i.e., it does not depe

GHC allow-overlapping-instances (PART II)

2003-10-03 Thread Kenny
Hi all, Here I change the instances from > instance C (OR T r) T > instance C (OR r T) T to > instance C (OR T r) T > instance C (OR T T) T and it compiles when allow-overlapping-instances is turned on. now I understand that GHC in fact allow-overlapping-instances if one is more s

GHC allow-overlapping-instances

2003-09-28 Thread H X
Hi, Does anyone have ever used this option? I see no difference when I present this program to ghc with -fallow-overlapping-instances on/off: module Test where data T = T data F = F data OR a b = OR a b data AND a b = AND a b class C a b | a -> b instance C (OR T r) T instance C (OR r T

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 F

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

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

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 &g

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
> f _ (_,c,_) = c > ghci -fglasgow-exts -fallow-overlapping-instances compiles it without > complaint but hugs -98 +o says: > ERROR "ClassProblem.hs":7 - Instances are not consistent with > dependencies > *** This instance: C a (a,b,c) b >

RE: overlapping instances and functional dependencies

2003-08-14 Thread Hal Daume
Behalf Of Wolfgang Jeltsch > Sent: Friday, August 08, 2003 4:33 PM > To: The Haskell Mailing List > Subject: overlapping instances and functional dependencies > > > Hello, > > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c &g

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

overlapping instances and functional dependencies

2003-08-10 Thread Wolfgang Jeltsch
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 -fallow-overlapping-instances compiles it withou

Re: Overlapping instances in existentials

2003-06-20 Thread oleg
ata Foo = forall x. (SubType x BaseType) => MkFoo x > | > | test :: Foo -> Value > | test (MkFoo x) = inj x I'm quite dubious that test can be typed at all (see below). Even if the problem with overlapping instances could be solved. I seem to remember being on this ro

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

Overlapping instances in existentials

2003-06-19 Thread Simon Peyton-Jones
[I'm widening this to the Haskell list, because overlapping instances are of general interest.] | To determine (SubType y Value) which is just: | (SubType y (Either Double BaseType)) | | it seems to me that GHC should (has to?) use |instance (SubType a b) => SubType a (

RE: frantk / overlapping instances

2000-09-01 Thread Mark P Jones
| does type-checking remain decidable (in general) for overlapping instances | (:+o in hugs)? Type checking in Hugs (with -98, at least) isn't decidable, either with or without overlapping instances! But decidability could be recovered by placing stronger syntactic requirements on the fo

Re: frantk / overlapping instances

2000-09-01 Thread Ch. A. Herrmann
Hello, does type-checking remain decidable (in general) for overlapping instances (:+o in hugs)? -- Christoph

Re: frantk / overlapping instances

2000-08-31 Thread Johannes Waldmann
> Overlapping instances for class "Bindable" > A suggestion for a direct fix would be nice, run it like this: hugs -h4m -98 +o ... -- -- Johannes Waldmann http://www.informatik.uni-leipzig.de/~joe/ -- -- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/252 -- ===>

frantk / overlapping instances

2000-08-31 Thread Timothy Docker
frantk/src/FranTkSrc/WidgetSetImpl.lhs" (line 64): Overlapping instances for class "Bindable" *** This instance : Bindable Canvas *** Overlaps with : Bindable (PWidget a) *** Common instance : Bindable Canvas A suggestion for a direct fix would be nice, but I can't attempt to work out w

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 >

Overlapping instances

2000-03-08 Thread Simon Peyton-Jones
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 what people agree about what they disagree

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

overlapping instances

2000-03-05 Thread S.D.Mechveliani
To my notes on the overlapping instances and deduced contexts Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes on 29 Feb 2000 >> If we want the recent implementations to compile this as needed, we >> have to write >> g :: (Eq a, Eq (Maybe

overlapping instances

2000-03-01 Thread S.D.Mechveliani
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes >> > 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 = length x

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
ension which caused the compiler to pass 10 instances instead of 2 to my functions (that don't use the extension of overlapping instances). Third, it does not work well with local universal quantification: data A = A (forall a. Eq a => [a] -> a) I want to be able to say "W f" w

overlapping instances

2000-02-29 Thread S.D.Mechveliani
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote on overlapping instances > 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 overloade

overlapping instances

2000-02-28 Thread S.D.Mechveliani
To my recent propaganda for the overlapping instances Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes on 27 Feb 2000 >> module G (g) >> where >> g:: Eq a => (a -> Bool) -> [a] -> [Bool] >> g h xs = map h xs

Re: overlapping instances

2000-02-27 Thread Marcin 'Qrczak' Kowalczyk
Eq a in its context. From what Jeffrey R. Lewis said, I assume that it will no longer compile.) Type signatures must contain more detailed contexts to make overlapping instances work: they must not be ever reduced from Eq (Maybe a) to Eq a. Prohibiting such reductions indeed helps, makes glo

overlapping instances

2000-02-27 Thread S.D.Mechveliani
I feel now that the overlapping instances are, generally, all right in Haskell. Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> had set certain example to show their inconsistensy. In my last letter I admitted that this example presented a problem. But now, I think there is no

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
,"baz"] > compiles to f_compiled eqChar eqMaybeString ["foo","bar","baz"]. > > Hence, ignoring so far various optimization possibilities, we see > that f is compiled *once*. But each its application requires the > appropriate dictionary val

Re: overlapping instances

2000-02-24 Thread Jeffrey R. Lewis
is an interesting idea, but essentially orthogonal to overlapping instances. I.e., making signature contexts optional would in this case make overlapping instances more convenient, and that's all. I'm not willing to have this be the default behavior for Haskell, but others have already pr

Re: overlapping instances

2000-02-24 Thread Marcin 'Qrczak' Kowalczyk
in g1,g2 with both dictionary values for eqMb > and choose the one of the most special instance at the run-time. > It this hard to implement? I don't know, but it would mean that all parts of the program, even those that won't ever be called with types that depend on overlapping in

overlapping instances

2000-02-24 Thread S.D.Mechveliani
I thank Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> for the helpful example on the subject of overlapping instances. The example was against the overlapping instances. And the whole discussion aims to investigate to what extent the overlaps can be treated consistently in Ha

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

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

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 >

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

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

overlapping instances

2000-02-16 Thread S.D.Mechveliani
es, then the instances are agreed automatically. >> Something hard to understand. I do not see why one has to play >> these strange tricks instead of introducing most natural overlapping >> instances. > Do you say that the function with the type > f :: Eq a => [a] -&g

Re: overlapping instances

2000-02-15 Thread Marcin 'Qrczak' Kowalczyk
uot;instance C X", and adding instance B X where ... makes it use another. > Maybe, overlaps does not change radically the situation. In any > case, when the compiler sees some operation op of class C in the > module M, one has to find the instance(s) for C in the modules >

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

overlapping instances

2000-02-15 Thread S.D.Mechveliani
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes on 14 Feb 2000 > [..] > overlapping instances don't solve what they seemed to claim to solve: > > classA a where ... > class A a => B a where ... > classC a where ... > > ins

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

Re: overlapping instances

2000-02-14 Thread Marcin 'Qrczak' Kowalczyk
another class)? > > In what way it constrains what else we can do with a type? I think I was a bit mistaken about how ghc handles overlapped instances. However in the following case there is an ambiguity that I don't know how to resolve - overlapping instances don't solve what they s

overlapping instances

2000-02-11 Thread S.D.Mechveliani
Juergen Pfitzenmaier <[EMAIL PROTECTED]> writes on 9 Feb 2000 > Maybe I understand why Sergey wants to use overlapping instances in his > DoCon. 2 years ago I tried to the same thing in C++ (also while implementing > a computer algebra system). Overlapping instances *may* be u

overlapping instances

2000-02-10 Thread S.D.Mechveliani
I continue arguing for the overlapping instances. To my >> It may know how to compute an operation in a more efficient way in >> the special case, and in a less efficient way in the generic case. Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes on 6 Feb 2000

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 lea

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 ins

Re: overlapping instances

2000-02-07 Thread Jeffrey R. Lewis
research.microsoft.com/users/simonpj/Papers/multi.ps.gz> > Section 4.4 > > 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 Marcin 'Qrczak' Kowalczyk
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 actually used. -- __("<Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl

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

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.

overlapping instances

2000-02-06 Thread S.D.Mechveliani
To my notes on overlapping instances >> [..] >> In my case, it was not so bad. The results were different in a weaker >> sense. It was like this: >> card z5 --> Fin 5 >> "integers modulo 5 has finite card

seek help with overlapping instances

1999-08-19 Thread Marko Schuetz
I have something similar to > class (Eq a) => Substitutable a where > match :: a -> a -> Maybe (Substitution a) > applySubst :: Substitution a -> a -> a and two Types Type1, Type2, both of which are instances of class Substitutable. In some places there is a sigma :: Substitution Type1 (or a

RE: seek help with overlapping instances

1999-08-19 Thread Mark P Jones
line flag). In short, it works by delaying the check for overlapping instances, and using the contexts of two potentially overlapping instances to distinguish between them. If only one instance applies, then things will work as you intended. However, if multiple instances apply, then you'll get a type error, as before. All the best, Mark

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 manu

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

Overlapping instances?

1999-06-13 Thread Kevin Atkinson
Could some one explain to me why this is OK: class T f r instance T a (a) instance T (c a b) (c a (b)) but this is not: class T f r instance T a (d a) instance T (c a b) (c a (d b)) as Hugs gives (with -98 +o) ERROR "T.hs" (line 4): Overlapping instances