TypeFamilies vs. FunctionalDependencies & type-level recursion

Dan Doel wrote:
class C a b | a -> b where foo :: a -> b foo = error "Yo dawg."
instance C a b where
The instance 'C a b' blatantly violates functional dependency and should not have been accepted. The fact that it was is a known bug in GHC. The bug keeps getting mentioned on Haskell mailing lists about every year. Alas, it is still not fixed. Here is one of the earlier messages about it: http://www.haskell.org/pipermail/haskell-cafe/2007-March/023916.html HList does NOT depend on that invalid behavior. The bug is relatively recent (introduced around 2006); HList worked in 2004.

| > class C a b | a -> b where | > foo :: a -> b | > foo = error "Yo dawg." | > | > instance C a b where | | The instance 'C a b' blatantly violates functional dependency and | should not have been accepted. The fact that it was is a known bug in | GHC. The bug keeps getting mentioned on Haskell mailing lists | about every year. Alas, it is still not fixed. Here is one of the | earlier messages about it: | | http://www.haskell.org/pipermail/haskell-cafe/2007-March/023916.html Wait. What about instance C [a] [b] ? Should that be accepted? The Coverage Condition says "no", and indeed it is rejected. But if you add -XUndecidableInstances it is accepted. It's just the same for instance C a b It is rejected, with the same message, unless you add -XUndecidableInstances. Do you think the two are different? Do you argue for unconditional rejection of everything not satisfying the Coverage Condition, regardless of flags? Simon

On Wed, Jun 15, 2011 at 3:25 AM, Simon Peyton-Jones
Wait. What about instance C [a] [b] ? Should that be accepted? The Coverage Condition says "no", and indeed it is rejected. But if you add -XUndecidableInstances it is accepted.
This 'clearly' violates the functional dependency as well. However, I must admit, it surprises me that GHC or Hugs ever detected this, and I imagine there's no general way to detect 'acceptable' instances.
Do you think the two are different? Do you argue for unconditional rejection of everything not satisfying the Coverage Condition, regardless of flags?
One obvious difference from the instances that appear (depending on how smart you're pretending to be as a compiler) bad but are nevertheless okay is that these have no contexts. If you can detect that, then: instance C a b instance C [a] [b] clearly have multiple independent instantiations on both sides, and so the relation is clearly non-functional. A simple heuristic might be to reject those, but allow: instance (..., D .. b .., ...) => C a b trusting that the context determines b in the right way. Is this possibly what GHC used to do? Of course, that allows 'Show b => C a b' so it's pretty weak. A slightly more intelligent heuristic might be to see if the fundeps in the context determine b, but that sounds like it might be leaving the realm of what's checkable. -- Dan

Hello,
On Wed, Jun 15, 2011 at 12:25 AM, Simon Peyton-Jones
| > class C a b | a -> b where | > foo :: a -> b | > foo = error "Yo dawg." | > | > instance C a b where | | The instance 'C a b' blatantly violates functional dependency and | should not have been accepted. The fact that it was is a known bug in | GHC. The bug keeps getting mentioned on Haskell mailing lists | about every year. Alas, it is still not fixed. Here is one of the | earlier messages about it: | | http://www.haskell.org/pipermail/haskell-cafe/2007-March/023916.html
Wait. What about instance C [a] [b] ? Should that be accepted? The Coverage Condition says "no", and indeed it is rejected. But if you add -XUndecidableInstances it is accepted.
It's just the same for instance C a b It is rejected, with the same message, unless you add -XUndecidableInstances.
Do you think the two are different? Do you argue for unconditional rejection of everything not satisfying the Coverage Condition, regardless of flags?
No, those two are not different, the instance "C [a] [b]" should also be rejected because it violates the functional dependency. The fact that -XUndecidableInstances accepts this is exactly the bug that keeps being mentioned on the lists every now and then. The reason that this instance violates the functional dependency is that it allows us to conclude both "C [Int] [Bool]", and "C [Int] [Char]", and clearly "[Int] = [Int]", but "[Bool] /= [Char]". The general rule defining an FD on a class like "C" is the following logical statement: "forall a b1 b2. (C a b1, C a b2) => (b1 = b2)" (So I think that the basic concept is really very simple and precise. I agree that the implementation can be tricky, but a lot of the difficulties are shared with type families---we are just dealing with a hard problem.) With simple instances (no contexts) it is easy to check if a set of instances is consistent with the FDs of the classes, however when we have conditional instance the task is harder. This is why we have approximations that ensure consistency (e.g., the Coverage Condition). My understanding is that the coverage condition in GHC ensures both consistency with the FDs, and termination of the process. In the past we had another condition, which ensured consistency but not necessarily termination (I forget its name now but, basically, the rule said that all variables in the target of an FD should be determined from the variables in the source of the FD, but we can use FDs in the context of the instance). I think the GHC bug is that with -XUndecidableInstances, instances are not validated at all wrt to FDs. A way to fix that would be to switch to using the old FD validation rule when -XUndecidableInstances are turned on. -Iavor Simon
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

At Wed, 15 Jun 2011 10:10:14 -0700, Iavor Diatchki wrote:
Hello,
On Wed, Jun 15, 2011 at 12:25 AM, Simon Peyton-Jones
wrote: | > class C a b | a -> b where | > foo :: a -> b | > foo = error "Yo dawg." | > | > instance C a b where
Wait. What about instance C [a] [b]
No, those two are not different, the instance "C [a] [b]" should also be rejected because it violates the functional dependency.
But now you are going to end up rejecting programs like this: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} class C a b | a -> b class D a b | a -> b instance (D a b) => C [a] [b] And a lot of useful code (including HList) depends on being able to do things like the above.
The fact that -XUndecidableInstances accepts this is exactly the bug that keeps being mentioned on the lists every now and then. The reason that this instance violates the functional dependency is that it allows us to conclude both "C [Int] [Bool]", and "C [Int] [Char]", and clearly "[Int] = [Int]", but "[Bool] /= [Char]".
If, instead of FunctionalDependencies, the extension were called ChooseInstancesWithoutKnowingAllTypeVariables, would you still have this objection? In other words, is the problem that the name FunctionalDependencies conveys the wrong intuition and makes it sound like classes should behave like non-polymorphic functions, or do you think there is something inherently problematic (beyond non-termination of the type checker) with lifting the coverage condition? I mean it's easy to get the behavior you want from FunctionalDependencies. All you have to do is declare an instance for a ground type. But conversely, if you eliminated the ability to lift the coverage condition, all kinds of useful stuff would no longer be possible. Particularly since type safety is not the issue here, I'd rather have the more general option available.
The general rule defining an FD on a class like "C" is the following logical statement: "forall a b1 b2. (C a b1, C a b2) => (b1 = b2)"
And in fact b1 and b2 are equal, up to alpha-conversion. They are both just free type variables. Suppose instead we had the following code: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} class C a b | a -> b where getb :: a -> b instance C Bool Int where getb _ = 0 instance C Char [b] where getb _ = [] instance C Int [b] where getb _ = [] We are saying that when a is a bool, getb gets you an Int. When a is a Char or an Int, getb returns a list of any type that you want. What's so wrong with that? Really this boils down to the question of whether it makes sense to say that non-ground types can be equal. I think it does. Consider the following two functions: f1 :: String -> a f1 = error f2 :: String -> b f2 = error Doesn't it make sense to say that f1 and f2 have the same type, even though, yes, for f1 the free type variable happens to be called "a", and for f2 it happens to be called "b"?
With simple instances (no contexts) it is easy to check if a set of instances is consistent with the FDs of the classes, however when we have conditional instance the task is harder. This is why we have approximations that ensure consistency (e.g., the Coverage Condition). My understanding is that the coverage condition in GHC ensures both consistency with the FDs, and termination of the process. In the past we had another condition, which ensured consistency but not necessarily termination (I forget its name now but, basically, the rule said that all variables in the target of an FD should be determined from the variables in the source of the FD, but we can use FDs in the context of the instance).
I think you are thinking of the Paterson condition and the Coverage condition. They are both still required, and both simultaneously lifted by -XUndecidableInstances. See here: http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/type-class-exten... David

Hello,
On Wed, Jun 15, 2011 at 10:49 AM,
At Wed, 15 Jun 2011 10:10:14 -0700, Iavor Diatchki wrote:
Hello,
On Wed, Jun 15, 2011 at 12:25 AM, Simon Peyton-Jones <
simonpj@microsoft.com>
wrote:
| > class C a b | a -> b where | > foo :: a -> b | > foo = error "Yo dawg." | > | > instance C a b where
Wait. What about instance C [a] [b]
No, those two are not different, the instance "C [a] [b]" should also be rejected because it violates the functional dependency.
But now you are going to end up rejecting programs like this:
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-}
class C a b | a -> b class D a b | a -> b instance (D a b) => C [a] [b]
And a lot of useful code (including HList) depends on being able to do things like the above.
Nope, this program will not be rejected because "b" is in the FD closure of "a". This stuff used to work a few GHC releases back, and I think that this is the algorithm used by Hugs. A functional dependency on a class imposes a constraint on the valid class instances (in a similar fashion to adding super-class constraints to a class). In general, checking this invariant may be hard, so it is fine for implementations to be "incomplete" (i.e., reject some programs that do satisfy the invariant or, perhaps, fail to terminate in the process). OTOH, I think that if an implementation accepts a program that violates the invariant, then this is a bug in the implementation.
The general rule defining an FD on a class like "C" is the following logical statement: "forall a b1 b2. (C a b1, C a b2) => (b1 = b2)"
And in fact b1 and b2 are equal, up to alpha-conversion. They are both just free type variables.
No, this was intended to be a more "semantic" property. Here it is in English: For any three ground types "a", "b1", and "b2", if we can prove that both "C a b1" and "C a b2" hold, then "b1" and "b2" must be the same type. The theory of functional dependencies comes from databases. In that context, a class corresponds to the schema for a database table (i.e., what columns there are, and with what types). An instance corresponds to a rule that adds row(s) to the table. With this in mind, the rule that I wrote above exactly corresponds to the notion of a functional dependency on a database table. -Iavor

At Wed, 15 Jun 2011 16:54:24 -0700, Iavor Diatchki wrote:
> | > class C a b | a -> b where > | > foo :: a -> b > | > foo = error "Yo dawg." > | > > | > instance C a b where > > Wait. What about > instance C [a] [b] > > No, those two are not different, the instance "C [a] [b]" should also be > rejected because it violates the functional dependency.
But now you are going to end up rejecting programs like this:
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-}
class C a b | a -> b class D a b | a -> b instance (D a b) => C [a] [b]
And a lot of useful code (including HList) depends on being able to do things like the above.
Nope, this program will not be rejected because "b" is in the FD closure of "a". This stuff used to work a few GHC releases back, and I think that this is the algorithm used by Hugs.
What do you mean "b" is in the FD closure of A (particularly since the code above does not contain any instances of class D)? Would you also disallow the following code on the grounds that b is not in the FD closure of a'? class C a a' b | a a' -> b class D a b | a -> b instance (D a b) => C [a] [a'] [b] What about the following? class C a b | a -> b, b -> a instance C [a] [a] Can you give a specific example of code that you believe worked in GHC a few releases back but that doesn't work now (or vice versa)? I still don't understand if you object to the name FunctionalDependencies, or if you think there's something inherently bad with allowing code such as the above.
A functional dependency on a class imposes a constraint on the valid class instances (in a similar fashion to adding super-class constraints to a class).
Exactly. It's a constraint on *instances*, not on classes or types. It says that in a situation such as the following: class C a b | a -> b You can define "instance C Int Bool", or "instance C Int Char", or even "instance C Int a". But you cannot define more than one such instance, because for a given first argument, whatever you use as the second argument has to be unique (up to alpha conversion). If you want, you can even define overlapping instances, so long as they agree in the final argument: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE FlexibleInstances #-} class C a b | a -> b instance C (m a) [b] instance C (Maybe a) [c] -- alpha-conversion is okay, because -- (forall b. [b]) ~ (forall c. [c]) Once you've bought into OverlappingInstances and FunctionalDependencies, ruling out code such as the above is akin to ruling out functions such as "error :: String -> a". You can object that, hey, error is not a function! I mean, if I call it twice on the exact same argument, I get two different things back: error "Same" :: Int error "Same" :: Bool But it's more useful to think of error as returning bottom, which has all types, and to think of error's type signature as saying: "for a given argument, you always get back the same thing, but that thing happens to have all possible types." Would you be happier if I used bottom as a type variable? class C a b | a -> b where f :: a -> b instance C [a] [bottom] where f _ = [] There's only one function f here. It always returns the same list. But that list happens to be a valid list of every possible type.
For any three ground types "a", "b1", and "b2", if we can prove that both "C a b1" and "C a b2" hold, then "b1" and "b2" must be the same type. The theory of functional dependencies comes from databases. In that context, a class corresponds to the schema for a database table (i.e., what columns there are, and with what types). An instance corresponds to a rule that adds row(s) to the table. With this in mind, the rule that I wrote above exactly corresponds to the notion of a functional dependency on a database table.
I think we are going around in circles. Is the point to be faithful to the database community, or to make it easier to program? UndecidableInstances, in their current form, pose no danger of making it into the Haskell standard, but they do make it easier to program, sometimes drastically reducing code size or clutter, eliminating boilerplate, and making code less error-prone. I don't think anyone is disputing that they fill some unmet need. So why don't we fix the name, and not reduce polymorphism. But just to make sure people don't agree with me too quickly, here's a more elaborate example that should make the non-believers scream: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE FlexibleInstances #-} class C a b | a -> b instance C [a] [b] instance C [m a] [Either b c] instance C [[a]] [Either a c] David

First of all, I do agree with David. Overlapping instances are indeed very useful in practice, cutting down significant amount of boiler-plate. His examples, as well the example from polymorphic map libraries (mentioned earlier) are real-world cases where overlapping instances are invaluable and indispensable. I do wish to point out the need for `proper credit': is the benefit specifically because of overlapping, or functional dependencies alone suffice? As far as I noticed, all compelling examples used and relied on overlapping instances (not just functional dependencies or undecidable instances) The functional dependencies per se are quite well understood: see The theory of overloading Peter J. Stuckey and Martin Sulzmann TOPLAS, 2005, v27, N6, 1216--1269 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.8.837 (perhaps there is a better URL, to the final version of the paper) Language and Program Design for Functional Dependencies Mark P. Jones, Iavor S. Diatchki http://web.cecs.pdx.edu/~mpj/pubs/fundeps-design.html `The theory of overloading' should answer Dan Doel's question about the ideal way of handling functional dependencies. The paper should also answer all of David's questions about functional dependencies, explaining why Iavor and I so object to class C a b | a -> b instance C a b It is the overlapping instances that muddy the water (especially in combination with other Haskell features such as higher-rank types). There is a nagging feeling that the combination may even be unsound. But the overlapping instances are so useful and compelling! That is exactly the problem that started this thread, as I understand. I do wish to stress the solution I have proposed earlier. I think it helps implement all of David's examples (and all of mine examples), without overlapping instances. Whether one uses functional dependencies or type functions is a secondary, and minor issue. The solution could be implemented (in ugly way) even now, but will benefit from _small_ GHC support. There are NO changes to GHC core or to the FC calculus are required. David wrote:
class C a b | a -> b where aDefault :: a aTobC :: a -> b class D a b where -- no fundep aTobD :: a -> b instance (D Int b) => C Int b where -- should this be allowed? aDefault = 0 aTobC = aTobD
class C' a b | a -> b class E a b | a -> b -- unlike above, we now have a fundep instance (E a b) => C' a b
Oleg, you haven't weighed in this specific question, but I think many of your ideas require the ability to write instances like C', even if you advocate disallowing C.
I would argue for rejection of the instance of C but accepting C'. The Prolog program posted yesterday will back me up. I should stress the underlying reason. First of all, when considering if an instance violates functional dependency, the methods of the instance are irrelevant. Only the instance head and its constraints matter. Here is why. Recall the main property: (C a b1, C a b2) ==> b1 ~ b2 Here is the corollary: given instance C Int Bool and the type forall t. C Int t => t we _improve_ the type to just Bool. The type equality constraint t ~ Int lets us replace all occurrences of the variable t with Int. This is exactly the sort of substitution that underlies lambda-calculus. Thus, the process of improvement simulates general computation. Thus functional dependencies let us write and run type-level programs.

I fully agree with Iavor. The correctness criterion is the declaration class C a b | a -> b implies that the following implication must hold: C a1 b1, C a2 b2, a1 ~ a1 ===> b1 ~ b2 That implication lets us derive the proof of type equality, which we can use for improving other types and resolving further constraints. Here is a little Prolog program that helps us decide which instance declarations should be accepted, and which are in error (regardless of the Undecidable instances flag). The program currently works when there is no overlapping. The program is a simple model checker for the above implication. Ex1: % class C a b | a -> b % instance C Int Bool % instance C a b c(int,bool). c(_A,_B). ?- c(X,Y), c(X,Y1), disunify(Y,Y1), print(['counterexample: ', c(X,Y), c(X,Y1)]). %% [counterexample: , c(int, bool), c(int, e7)] A counter-example was found. The instances must be rejected. Ex2:
Wait. What about instance C [a] [b]
% class C a b | a -> b % instance C Int Bool % instance C [a] [b] c(int,bool). c([_A],[_B]). ?- c(X,Y), c(X,Y1), disunify(Y,Y1), print(['counterexample: ', c(X,Y), c(X,Y1)]). %% [counterexample: , c([_G2442], [e8]), c([_G2442], [e9])] Reject. Ex3: % class C a b | a -> b % instance C Int Bool % instance C [a] a c(int,bool). c([_A],_A). ?- c(X,Y), c(X,Y1), disunify(Y,Y1), print(['counterexample: ', c(X,Y), c(X,Y1)]). %% No counter-examples. Accept. Ex4:
What about the following code--do you think this should be illegal, too? class C a b c | a -> b where instance C (Maybe a) (Maybe b) (Maybe b) where
c(maybe(_A),maybe(_B),maybe(_B)). ?- c(X,Y,Z), c(X,Y1,Z1), disunify(Y,Y1), print(['counterexample: ', c(X,Y,Z), c(X,Y1,Z1)]). %% [counterexample: , c(maybe(_G2446), maybe(e11), maybe(e11)), %% c(maybe(_G2446), maybe(e12), maybe(e12))] Illegal. Ex5:
But now you are going to end up rejecting programs like this: class C a b | a -> b class D a b | a -> b instance (D a b) => C [a] [b]
d(int,bool). % Need an instance for D; otherwise, we won't type check. c([A],[B]) :- d(A,B). ?- c(X,Y), c(X,Y1), disunify(Y,Y1), print(['counterexample: ', c(X,Y), c(X,Y1)]). %% Failed, no counter-examples. Accepted. Ex6: %% class C a a' b | a a' -> b %% class D a b | a -> b %% instance (D a b) => C [a] [a'] [b] d(int,bool). % Need an instance for D; otherwise, we won't type check. c([A],[A1],[B]) :- d(A,B). ?- c(X,Y,Z), c(X1,Y1,Z1), [X,Y] = [X1,Y1], disunify(Z,Z1), print(['counterexample: ', c(X,Y,Z), c(X1,Y1,Z1)]). %% Failed to find a counter-example. Accept. Here is the definition of disunify. eigen(X) :- gensym(e,X). % Ground a term, instantiating all of its variables to fresh constants instantiate(T) :- term_variables(T,Vars), maplist(eigen,Vars). % disunify(T1,T2) % Holds if T1 and T2 are not unifiable, or can be made non-unifiable. % If succeeds, T1 and T2 are ground and T1 \= T2. disunify(T1,T2) :- instantiate(T1), copy_term(T2,T21), (T1 = T21 -> instantiate(T2), \+ (T1=T2); true).

Okay, we seem to be having a debate where, to caricature only a little, I'm arguing that Fundeps/UndecidableInstances are ugly but useful, and other people are arguing that they are truly absolutely horrible in their current GHC implementation. I think the debate boils down to where you see the scope of the implicit universal quantification of free type variables in instances. Consider the following: class C a b | a -> b where aDefault :: a aTobC :: a -> b class D a b where -- no fundep aTobD :: a -> b instance (D Int b) => C Int b where -- should this be allowed? aDefault = 0 aTobC = aTobD GHC accepts this above code, which makes sense to me because I read the instance declaration as essentially (in pseudo-Haskell): forall b. instance (D Int b) => C Int b or, equivalently: instance C Int (forall b. (D Int b) => b) In English, "there's only one instance of C with (a ~ Int), but, in that instance, the aTobC method returns a value of type b for any b you want, except that in order to produce the value, it needs access to an appropriate dictionary of class D." One corollary of this view is that it is impossible to violate functional dependencies without defining more than one instance of a class. The alternate reading (and please correct me if I'm mis-characterizing the argument), is that we should apply the functional dependencies of a class to each individual instance, where any universal quantification happens across the fundep. According to this view, we should read C's instance declaration as: forall b. (instance (D Int b) => C Int b | Int -> b) and find that "forall b. ... | Int -> b" fails. Hence, we have violated functional dependencies with a single instance of the class. There's a less explicit but equally important question underlying this discussion about how much contexts should play into instance validation. Some have suggested GHC should reject the above instance of C, but should nonetheless accept the following instance of C': class C' a b | a -> b class E a b | a -> b -- unlike above, we now have a fundep instance (E a b) => C' a b Oleg, you haven't weighed in this specific question, but I think many of your ideas require the ability to write instances like C', even if you advocate disallowing C. On this question, I am opposed, because I find it too reminiscent of an aspect of C++ I dislike, namely that ad-hoc polymorphism interacts with templates, implicit promotion, and the most-specific match rule to make it hard to understand code. (And since, unlike C++, Haskell allows polymorphic return types, there's a potential for things to get even more complicated.) Fortunately, GHC's current approach is quite simple: The instance head is always sufficient to determine whether or not an instance matches, two instances overlap, or functional dependencies are violated. The context may tell you what dictionaries must be around if you actually want to use an instance, but if you know that a program compiles, you can ignore the context when reading and reasoning about the code. Another reason that I oppose too much reliance on the context is that I want the ability to load code dynamically. If the assumption about ground type equality is pushed too far--e.g., allowing coercion based on reasoning about fundeps--then dynamically loading modules with contradictory fundeps could undermine memory safety. One of my objections to type families is the difficulty of guaranteeing safety in the presence of dynamic loading. At any rate, this is the haskell-prime mailing list, not the how-much-do-you-hate-some-current-ghc-option-implementation list. I've already taken a lot of people's time with this thread, so let me propose to do something useful for the haskell prime effort. I could start a compilation (probably a wiki page) of things you can do or might want to do with fundeps and undecidable/overlapping instances. This could serve as a kind of wish list for Haskell prime. Examples off the top of my head might be: - Type-safe dynamic loading - Sqrt(N) reduction in code size for mtl instances - HList/OO-Haskell - Enforcing simple recursively-defined properties on types. (E.g., with GHC 7.2's new generic deriving framework, you might want to specify the constraint that a type's Representation doesn't include NoSelector.) - Using data types to represent ad-hoc polymorphic functions you can pass as arguments to functions. E.g., using a class like: class Function f a b | f a -> b where funcall :: f -> a -> b you can define types f of class Function and use them to do maps over tuples. Someone thinking of implementing an idea (e.g., closed type families) could look at the wish list and determine out how much of it the new feature would cover. Others could add to the wish list. Oleg, I realize the list might resemble your bibliography, but the idea would be to list the simplest possible cases (like C' above), rather than examples that unleash the full power of the extension. We can link to your web site for people who want to delve deeper into the motivation. If that sounds like a useful idea, the next question is where to put such a list. The Haskell prime wiki seems like a logical place, but it should be someplace where multiple people can edit it. (And, though I have an account on the Haskell prime wiki, username David, I can't seem to edit stuff there.) David

At Tue, 14 Jun 2011 19:52:00 -0700 (PDT), oleg@okmij.org wrote:
Dan Doel wrote:
class C a b | a -> b where foo :: a -> b foo = error "Yo dawg."
instance C a b where
The instance 'C a b' blatantly violates functional dependency and should not have been accepted. The fact that it was is a known bug in GHC. The bug keeps getting mentioned on Haskell mailing lists about every year. Alas, it is still not fixed. Here is one of the earlier messages about it:
http://www.haskell.org/pipermail/haskell-cafe/2007-March/023916.html
But Oleg, isn't what you are complaining about *exactly* the lifting of the coverage condition, which is one of the explicit points of -XUndecidableInstances? Are you advocating two separate switches for lifting Paterson vs. Coverage? What about the following code--do you think this should be illegal, too? {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE UndecidableInstances #-} class C a b c | a -> b where instance C (Maybe a) (Maybe b) (Maybe b) where David
participants (5)
-
Dan Doel
-
dm-list-haskell-prime@scs.stanford.edu
-
Iavor Diatchki
-
oleg@okmij.org
-
Simon Peyton-Jones