[GHC] #12240: Common Sense for Type Classes

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC erroneously reports that there is "No instance of C". But, in fact, there is an instance, `C Int Char`; furthermore, it is the only instance. So GHC should use it! {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} module T4921 where class C a b where f :: (a,b) instance C Int Char where f = undefined x = fst f y = fst f :: Int }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): No, it shouldn't. Is this a request for a better error message? May be a duplicate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314): This is a request to allow instance dispatch to make inferred types more specific. I still think this should compile, and I even have a GHC branch where it does. It is quite simple; you just have to change `tcMatchTys` to `tcUnifyTys`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): If you want refinement of this type to occur, you need to use a functional dependency, ala: {{{ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} module T4921 where class C a b | a -> b where f :: (a,b) instance C Int Char where f = undefined -- x = fst f y = fst f :: Int }}} Otherwise, a user can legally, WITHOUT `IncoherentInstances`, define another `instance C Int Int` which would cause the instance resolution to be ambiguous. Maybe we can make the error message better though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314): Functional dependencies imply too much structure. Consider {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} class C a b instance C Int Bool instance C Int Char instance C Word8 String instance C Word16 String }}} If we have `instance C a Bool`, we know that `a ~ Int`. But if we have `instance C Word8 b`, we know `b ~ String`. Functional dependencies cannot express this logic, but it is still "common sense logic". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314): I discussed the proposal with some people on IRC, and the consensus seems to be that, while nobody besides me thinks that implementing this is particularly useful (or possible), they would not immediately reject an implementation. I have started work on this in https://github.com/Mathnerd314/ghc. I am also planning to solve #11948 "correctly" in the same branch, as outlined in the OutsideIn(X) paper:
... the behavior of the solving algorithm [with respect to dictionary instantiation] remains non-deterministic. This [can be fixed] by refraining from applying DINSTW if a local given could match with the wanted constraint (perhaps after instantiating unification variables)
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) Comment: This is only "common sense" if you discard the open world assumption (or accept incoherence), neither of which are particularly palatable. I don't claim to have any say in whether an implementation will or will not be accepted, but bear in mind that new features have an ongoing cost, even if guarded by language flags. Feel free to work on it if you like, but seeking wider input first might be a good idea to avoid working on something that is ultimately not merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314):
This is only "common sense" if you discard the open world assumption
I have not seen hide nor hair of this fabled "open world assumption", except a small section in Real World Haskell:
We can add new instances anywhere; they are not confined to the module where we define a typeclass. This feature of the typeclass system is referred to as its open world assumption.
This refers to the ''declaration'' of instances, not instance resolution. If the proposal was to remove orphan instances, I would see the merit of bringing this up, but it does not seem relevant here.
(or accept incoherence),
Consider this: {{{#!hs -- in A.hs class A a where f :: a -> Int -- in B.hs instance A Int where f _ = 1 foo = f (0 :: Int) -- in C.hs instance A Int where f _ = 2 bar = f (0 :: Int) -- in Main.hs main = print (foo,bar) -- (1,2) }}} It is a blatant violation of the Haskell Report ("A type may not be declared as an instance of a particular class more than once in the program."), yet it compiles in GHC with no extensions. Meanwhile, all I want to do is relax instantiation from "a single instance matches and no other instance unifies" to "a single instance unifies and no other instance unifies". This is only interesting in limited situations, such as the example in comment:4, and leaves all Haskell 98 instances unchanged. I do not see how it adds any incoherence, because in both rules only a single instance is allowed.
I don't claim to have any say in whether an implementation will or will not be accepted, but bear in mind that new features have an ongoing cost, even if guarded by language flags. Feel free to work on it if you like, but seeking wider input first might be a good idea to avoid working on something that is ultimately not merged.
I have posted on Reddit, IRC, and this bugtracker; what's left besides Phabricator? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Two quite separate reactions to this: 1. You can already do what you want, if you rephrase your instance. From the initial post: {{{#!hs instance (a ~ Int, b ~ Char) => C a b where ... }}} will have the behavior you want. The idea is that you're creating a universal instance (i.e., one that matches any pair of types) but then GHC must solve `a ~ Int` and `b ~ Char`, which will unify your type variables. 2. As a "GHC Insider", I'm quite leery of blocking the door to "GHC Outsiders". See [https://www.reddit.com/r/haskell/comments/4isua9/ghc_development_outsidein/ this provocation] and [https://ghc.haskell.org/trac/ghc/blog/ContributingToGhc Simon's response]. I am in full agreement with Simon that we must do better here. However, adding a new feature to GHC is very, very expensive. Phabricator has well-written reasons why; see "Rejecting patches" on [https://secure.phabricator.com/book/phabcontrib/article/contributing_code/ this page]. (My reference to Phab here is technically unrelated to GHC's use of Phab. It's just that Phab is another open source project, and its articulation of barriers to entry is much more advanced than GHC's.) At the moment, the original poster has gotten other member of the community to say that they wouldn't actively block the implementation of your idea; I'm afraid this is hardly a ringing endorsement. You ask about another place to post. I see a bunch of proposals go through [https://mail.haskell.org/mailman/listinfo/haskell-cafe Haskell- cafe], where the level of discourse is quite high (as with all Haskell venues I've seen -- a wonderful aspect of our community!). But I don't want you to waste time posting in yet another place, because I tend to doubt that your patch will be accepted without the support of some more prominent, long-standing members of our community. A final point here is that the door from "GHC Outsider" to "GHC Insider" is surely open. The best way to nudge your way in, I think, is to find a feature request that is smallish and already has support. Implement that feature. You'll learn a whole lot about the compiler, and hopefully make a friend or two in the process. Repeat. After a few patches, you'll be well on your way to "GHC Insider". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

1. You can already do what you want, if you rephrase your instance. From
#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314): Replying to [comment:8 goldfire]: the initial post:
{{{#!hs instance (a ~ Int, b ~ Char) => C a b where ... }}}
Phabricator has well-written reasons why; see "Rejecting patches" on [https://secure.phabricator.com/book/phabcontrib/article/contributing_code/
Sure, this works for the original, and the original can also be solved with functional dependencies (as in comment:3). Even the example in comment:4 could be done with equality constraints, `(a ~ Int) => instance C a Bool` and so on. The issue is the open-world problem; with such general instance heads, you cannot extend the class to have more instances without running into overlap problems. Whereas with my approach, instances can still be declared; they just mean that instance resolution will fail more often (which is already an expected side-effect of declaring instances). From what I can tell, there was no reason for the matching (instead of unifying) behavior to begin with; it was just "how type class matching worked", back in 1996. E.g. page 12 of https://courses.cs.washington.edu/courses/cse590p/06sp/multi.pdf mentions that matching uses one-way unification, but gives no explanation of why two-way unification was not chosen. Then on page 13 they state that constraints can be improved if they unify with a unique instance, but just say "it is not yet clear if it would improve enough useful programs to be worth the extra effort." this page]. "The Phabricator upstream is Phacility, Inc. We maintain total control over the project and roadmap. There is no democratic process, voting, or community-driven decision making. This model is better at some things and worse at others than a more community-focused model would be, but it is the model we operate under." I am not sure this describes GHC well; wiki:TeamGHC states "GHC's development as a whole is not led by any particular group, company, or individual."
At the moment, the original poster has gotten other member of the community to say that they wouldn't actively block the implementation of your idea; I'm afraid this is hardly a ringing endorsement.
My impression is that this is better than the reaction to other (implemented!) proposals, e.g. Foldable in the Prelude, which were actively opposed. This issue is a rather small, dark corner of the language, so few have the patience to discuss it. Furthermore, I have not really elaborated on my proposal, because I don't know enough of GHC internals to describe it accurately, so it is hard to actively support a nebulous concept. At least a patch can be judged on its merits. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

It is a blatant violation of the Haskell Report ("A type may not be declared as an instance of a particular class more than once in the
Meanwhile, all I want to do is relax instantiation from "a single instance matches and no other instance unifies" to "a single instance unifies and no other instance unifies". This is only interesting in
#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): program."), yet it compiles in GHC with no extensions. Yes, so it is a bug. See #2356. limited situations, such as the example in comment:4, and leaves all Haskell 98 instances unchanged. I do not see how it adds any incoherence, because in both rules only a single instance is allowed. Your proposal seems to even allow situations like {{{#!hs class C a b where f :: a -> Int instance C String () where f _ = 1 instance C String Bool where f _ = 2 }}} If the two instances are in different modules, the expression `f "a" :: Int` will type check but have value `1` or `2` depending on which module is imported. Yet the instances are not even overlapping. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

From what I can tell, there was no reason for the matching (instead of unifying) behavior to begin with; it was just "how type class matching worked", back in 1996. E.g. page 12 of https://courses.cs.washington.edu/courses/cse590p/06sp/multi.pdf mentions
* //no matter what other (legal) instance declarations are added//,
This issue is a rather small, dark corner of the language, so few have
#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): that matching uses one-way unification, but gives no explanation of why two-way unification was not chosen. Then on page 13 they state that constraints can be improved if they unify with a unique instance, but just say "it is not yet clear if it would improve enough useful programs to be worth the extra effort." I believe the reason is the open world assumption, i.e. allowing for instances to be added later without changing the solver behaviour. Also, it's not clear to me whether any theoretical properties have been studied for the type system with unification in place of matching. Note one of the conditions regarding Decision 8 on page 13 of the paper you cite (my emphasis): there is only one instance declaration that the constraint can be made to match in this way. This is much more restrictive than your proposal, and would indeed not apply to many programs (if any), so it indeed hardly seems worth it. the patience to discuss it. I respectfully disagree. You are suggesting a rather significant change to the type system, and I for one think it is very interesting to discuss its implications. Thank you for bringing it up! Please take all these comments in a spirit of constructive debate, and apologies if my previous comment was too blunt.
Furthermore, I have not really elaborated on my proposal, because I don't know enough of GHC internals to describe it accurately, so it is hard to actively support a nebulous concept. At least a patch can be judged on its merits.
Most people won't judge a patch at all, I'm afraid. ;-) We really need a clear specification of the feature, articulated independently of the details of the implementation. A wiki page is a good place to put this, and can link to this ticket and other discussions. A specification should outline the motivation for the feature, describe the changes to the type system (not just the type inference algorithm, although that may be helpful too), give plenty of examples, and mention potential problems with the extension. On a different tangent, consider this module: {{{#!hs class C a where foo :: a instance C Int where foo = 42 f _ = foo }}} What is the inferred type of `f`? Previously it would have been `C a => b -> a` but under your proposal it would be `b -> Int`, right? This means that enabling the extension might cause existing programs to cease to type-check. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

"The Phabricator upstream is Phacility, Inc. We maintain total control over the project and roadmap. There is no democratic process, voting, or community-driven decision making. This model is better at some things and worse at others than a more community-focused model would be, but it is
#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:9 Mathnerd314]: the model we operate under."
I am not sure this describes GHC well; wiki:TeamGHC states "GHC's
development as a whole is not led by any particular group, company, or individual." Point well taken. I guess I was specifically referring to this passage from that page: Unjustifiable Costs: We support code in the upstream forever. Support is enormously expensive and takes up a huge amount of our time. The cost to support a change over its lifetime is often 10x or 100x or 1000x greater than the cost to write the first version of it. Many uncoordinated patches we receive are "white elephants", which would cost much more to maintain than the value they provide. As an author, it may look like you're giving us free work and we're rejecting it as too expensive, but this viewpoint doesn't align with the reality of a large project which is actively supported by a small, experienced team. Writing code is cheap; maintaining it is expensive. In an ideal world, the GHC maintenance would be democratized. But that's not quite how it currently is (there's a fairly small group that do the regular maintenance) and so we have to guard the door carefully. Part of the reason that insiders' ideas are seen more favorably is that, once you've demonstrated the time and energy to be a regular contributor, it seems more likely that you will maintain the patch -- at least for a while. This lowers the cost of accepting the patch. Shifting direction a bit, we really do need a more open, inclusive process by which ideas (even ones without proper specifications, yet) can be debated by the community, so that it's clearer what the community reaction is. You're going to get a very self-selected slice of the community by debating here. It sounds (from Simon's blog post linked earlier) that there is such a process in the works, and I'm looking forward to learning more about it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Mathnerd314: For what it's worth, I think this is a very interesting proposal, and merits further investigation. Let me consider a slightly modified version of your original example: {{{ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} module T4921 where class C a b where f :: a -> b instance C Int Char where f = undefined g x = f (x :: Int) }}} What should the inferred type of `g` be? There seem to be two options: 1. `g :: C Int b => Int -> b`, which is the current behavior of GHC today. The reasoning goes like this, "While it is true that there is only one instance of C where a ~ Int today, in some later module someone could very well define `C Int Int`, in which case, egg on my face if I picked the original instance! Better leave it to the user of `g` to tell me which one they actually want." 2. `g :: Int -> Char`, which I believe is what you are proposing. The reasoning here is, "Well, based on the instances I can see, it's BLOODY WELL obvious that the only possible instance `f` could use is `C a b`. The resolution is unambiguous." In most cases, option (1) makes more programs typecheck, EXCEPT when there could be ambiguity, in which case the more specific type is desirable; e.g. if I say `show (g 2)` (what am I showing? With the instances I can see, the only thing possible is `Char`.) Actually, there is mechanism for dealing with this situation: defaulting. In Haskell98, the `default` declaration is a way of saying, "When I get an ambiguous type, please pluck out this type to solve the ambiguity and then go your merry way." What your proposal seems to suggest is an alternate way to do defaulting, by consulting the instance environment in question. Specifically, if I have an ambiguous type variable `v` which occurs in some class `C t1 v ...`, if there is only ONE choice of `v` which allows the instance resolution to go through, I should default `v` to that one! This would (also) solve the original problem in your ticket. But maybe you have an example where you wanted more specific instance resolution, even in the absence of ambiguity. I'd be quite interested to see it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314):
What should the inferred type of g be?
My preferred answer is (1). The reasoning is something like: * an untyped function binding... infer a type signature * f creates a constraint, so it's `g :: forall b. C Int b => Int -> b` * it typechecks - done This is distinct from `x = fst f` in the original example. There, `x` is a pattern binding and the monomorphism restriction applies. `x` cannot have a constraint in the inferred type, thus GHC is forced to choose an instance, in particular the `C Int Char` instance, and so the inferred type is `x :: Char`. Similarly, `show (g 2)` generates constraints `Show b, C a b, Num a`, which can either go into the given constraints or be solved, depending on the context.
What your proposal seems to suggest is an alternate way to do defaulting, by consulting the instance environment in question.
Defaulting happens in `simpl_top`, while instance resolution happens in `solveSimpleWanteds` in `simpl_loop`. There's a note explaining that defaulting used to be in `simpl_loop`, but doing it outside any implications fixed some programs. I wonder if, analogously, moving instance resolution out near defaulting would result in a similar improvement. It does seem clear that defaulting and top-level instance resolution are intimately entwined with the instance environment.
Specifically, if I have an ambiguous type variable v which occurs in some class C t1 v ..., if there is only ONE choice of v which allows the instance resolution to go through, I should default v to that one!
That doesn't sound quite right. For example: {{{#!hs class X a b c instance X [a] (Maybe a) Bool instance X [a] [a] Char x = (\(d :: Dict (X [a] (Maybe Int) b)) -> typeOf d) Dict -- wanted: x = "Dict (X [Int] (Maybe Int) Bool)" }}} I don't see how defaulting would turn `[a]` into `[Int]`, if it did something variable-by-variable. (Also note that defaulting as currently implemented only applies to one- parameter type classes) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12240#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC