[GHC] #11450: Associated types at wrong type in instance

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider {{{ class C x where type T x instance C (Either a b) where type T (Either b a) = b -> a }}} This is bogus, because the equation for `T` has the parameters to `Either` reversed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description:
Consider {{{ class C x where type T x
instance C (Either a b) where type T (Either b a) = b -> a }}} This is bogus, because the equation for `T` has the parameters to `Either` reversed.
New description: Consider {{{ class C x where type T x instance C (Either a b) where type T (Either b a) = b -> a }}} This is bogus, because the equation for `T` has the parameters to `Either` reversed. But GHC 8.0 RC1 (and master) allow it. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Lemming): * cc: ghc@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott):
This is bogus, because the equation for `T` has the parameters to `Either` reversed.
Interesting, I was not aware of such a restriction on type family instances. Is this documented somewhere in the [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/type- families.html users' guide section] on type families? I was under the impression that as long as the instantiated type in the associated instance was equal to the instance head up to alpha equivalence, then it would be accepted, i.e., the above example is a valid type family instance, but the following is rejected with an error: {{{#!hs class C x where type T x instance C (Either a b) where type T (Either b (f a)) = b -> f a }}} {{{ • Type indexes must match class instance head Found ‘Either b (f a)’ but expected ‘Either a b’ • In the type instance declaration for ‘T’ In the instance declaration for ‘C (Either a b)’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That would also make sense. So you would also like to be able to write {{{ class C v where type T v instance C (Either a b) where type T (Either x y) = y -> x }}} But I think the current intent is "equal" not "equal up to alpha equivalence". Which do people like best? I in the class decl you obviously must use the same `v`; that's how you link the associated type to its class. In the instance we could loosen it. It's a usability issue not a technical one. Which is best? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I think being able to use different type variables in the instance makes sense for a couple of reasons: 1. It's the way GHC has behaved for a while, so suddenly adding a new restriction feels questionable. I'm not sure if there's any code out there in the wild that relies on this behavior, but it wouldn't surprise me if there is. 2. You can already do things like this: {{{#!hs class C v where instance T x v y instance C (Either a b) where instance T a (Either a b) b = b -> a }}} That is, you can have other type variables mentioned in an associated type family that aren't from the class declaration (as long as at least one of the type variables is from the class). In that type instance, I don't know if it really makes sense to talk about a canonical ordering for the type variables. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I think it's best to require the variables to be the same. They are the same under the hood, so they should be the same on top of the hood, too. The fact that we didn't require this previously is a bug, in my opinion. I don't see how the example in comment:5 argues otherwise. Yes, instances should allow non-linear uses of variables, but I don't see that as related to this overall issue. I could see someone arguing about spurious code breakage here, but I'm not too worried. And the change they would have to make is fully backward compatible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): My question is: what exactly do we mean by "require the variables to be the same"? For example, would the following instance be rejected under this new rule? {{{#!hs class C v where type T v instance C (Either a b) where type T (Either _ b) = b }}} Also, what rules (if any) do we apply to non-linear type variables (like in the example above)? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It's simple. Consider {{{ class C v where type T a b v cd }}} In any instance declaration, the type in the `v` position of the `type` instance must be the same as in the instance header: {{{ instance ... => C ty where type T p q ty r s = <rhs> }}} I think we do (or at least should) also insist that `p`, `q`, `r`, `s` are distinct type variables, otherwise the type instance is more specific than the class instance, but that's a separate matter. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Should this be rejected? {{{#!hs class C x y where type T x y instance C (Either a b) (Maybe c) where type T (Either a b) (Maybe b) = a }}} GHC 8.1.20160117 gives: {{{ • Type indexes must match class instance head Found ‘Either a b’ but expected ‘Either a b’ • In the type instance declaration for ‘T’ In the instance declaration for ‘C (Either a b) (Maybe c)’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes its should be rejected, as stated by my rule above -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

It's simple. Consider {{{ class C v where type T a b v cd }}} In any instance declaration, the type in the `v` position of the `type` instance must be the same as in the instance header: {{{ instance ... => C ty where type T p q ty r s = <rhs> }}} I think we do (or at least should) also insist that `p`, `q`, `r`, `s` are distinct type variables, otherwise the type instance is more specific
#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:8 simonpj]: than the class instance, but that's a separate matter. Thank you for a formal description of what's going on, but I'm still confused about how this should behave w.r.t. wildcards. By the above rules, if you have {{{#!hs class Warning a where type T a instance Warning (Either a b) where ... }}} Then we'd have to do something like this: {{{#!hs instance Warning (Either a b) where type T (Either a b) = a }}} But this results in a warning on GHC 8.0! {{{ Defined but not used: type variable ‘b’ }}} And if you changed `b` to `_`, it would no longer follow the rules described above. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): It's not a big deal, but I prefer the proposed change too. In my mind, when I write an instance {{{ instance C (Either a b) where ... }}} I'm really writing an instance for `Either a b` for each pair of specific, but unknown, types `a` and `b`. According to the class declaration {{{ class C x where type T x }}} I'm supposed to provide the value of `T` on the specific type `Either a b`. If I write `type T (Either b a) = ...`, then I haven't met that obligation. This argument is somewhat flimsy in that type variables in the head of an instance don't actually scope over the instance body in Haskell 98; but we're already so far outside Haskell 98 with associated type families that I don't mind. (With ScopedTypeVariables instance head type variables do scope over the body, which is the behavior most people expect, I think.) It also just seems more practical: I might reasonably read `type T (...) = b -> a` and doze off over the argument of `T`, expecting a sensible author to have made it match the instance head. Surprise! Technically this is a breaking change, but I feel that on balance, authors will be more glad to learn about non-matching associated type heads, which were probably unintentional, than annoyed that their code broke. However, we should do it either quickly, before the next 8.0 RC, or leave it until 8.2. Nothing critical about this change that I can see, so better not to slip it in at the last minute of a release. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

It's simple. Consider {{{ class C v where type T a b v cd }}} In any instance declaration, the type in the `v` position of the `type` instance must be the same as in the instance header: {{{ instance ... => C ty where type T p q ty r s = <rhs> }}} I think we do (or at least should) also insist that `p`, `q`, `r`, `s` are distinct type variables, otherwise the type instance is more specific
#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:8 simonpj]: than the class instance, but that's a separate matter. We don't and I don't think we should. Isn't it okay to define multiple instances that refine the other parameters, like this (currently accepted)? {{{ class C v where type T v w instance C (Either a b) where type T (Either a b) Int = a type T (Either a b) Char = b }}} In fact you're not obliged to provide any equations for `T` at all (though we do warn in that case). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:11 RyanGlScott]:
[...]
Then we'd have to do something like this:
{{{#!hs instance Warning (Either a b) where type T (Either a b) = a }}}
But this results in a warning on GHC 8.0!
{{{ Defined but not used: type variable ‘b’ }}}
And if you changed `b` to `_`, it would no longer follow the rules described above.
GHC 8.0 does warn about that but it shouldn't. See #11451. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes to comment:11. I still say that the args to the type family should be identical to in the icnstance header, in the positions that are linked by the class decl. No wildcards. As to comment:13, yes that's right. We do allow that generality. (But we don't in the default decl of an associated type, in a class decl; I was confused.) Summary of long thread: the Description of this ticket is still right! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #11449, #11451 Comment: Oh, I wasn't aware of #11449 and #11451. Those are pretty important context for navigating this. I don't have any objection (in principle) to requiring that the class instance types be the same as the associate types. All I ask is please allow me to write something like this if I want to: {{{#!hs instance C (Either a _) where type T (Either a _) = a }}} I'm quite fond of using wildcard types wherever possible, and I'd hate to lose that due to this issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Re comment:16: But your two wildcards are referring to the same type. I think we should require a name here, because the name is actually used twice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Re comment:16: But your two wildcards are referring to the same type. I
#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:17 goldfire]: think we should require a name here, because the name is actually used twice. I suppose if we take interpret every occurrence of `_` as a fresh type variable, then the `Either a _` in the instance head cannot be the same as the one in the associated type family instance. And there's even another reason to require named type variables: what about `-XInstanceSigs`? If you allowed wildcards in instances, you could have a scenario like this: {{{#!hs class C a where c :: a -> String instance C (Maybe _) where c :: Maybe _ -> String c _ = "huh?" }}} And we certainly don't allow wildcards in term-level type signatures like this. In light of this, I retract my objection in comment:16. As Simon said, the description of the ticket is still right. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #11449, #11451 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The patch in comment:19 does not resolve the ticket; it's just groundwork. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -2,1 +2,1 @@ - {{{ + {{{#!hs New description: Consider {{{#!hs class C x where type T x instance C (Either a b) where type T (Either b a) = b -> a }}} This is bogus, because the equation for `T` has the parameters to `Either` reversed. But GHC 8.0 RC1 (and master) allow it. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * failure: None/Unknown => GHC accepts invalid program * milestone: 8.0.1 => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.0.2
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11449, #11451 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: indexed- invalid program | types/should_fail/T11450 Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed-types/should_fail/T11450 * resolution: => fixed Comment: OK I've finally dealt with this one. I decided to tighten the rules, so that a `type instance` for an associated type, nested in a class `instance` declaration, must have an LHS that precisely matches the template laid out in the `class` declaration: * The arg positions that correspond to class type variables must be exactly as in the instance header * The other arg positions must be distinct type variables. That means you can no longer give ''multiple'' `type instance` decls for the same associated type in one `instance` decl. For example: {{{ class C a where type F a b instance C Int where type F Int Bool = Char type F Int Char = Bool }}} This is now illegal: the second arg position must be a variable. It's pretty weird anyway because the second arg position is open, so matching is incomplete. If you want something like that, use an auxiliary definition: {{{ instance C Int where type F Int b = FInt b type family FInt b type instance FInt Bool = Char type instance FInt Char = BOol }}} If the second arg is a closed type, you can use a closed type family definition, even better. This is a behaviour change -- but it's onle that the user manual explicitly signaled as subject to change. Don't merge to 8.0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: indexed- invalid program | types/should_fail/T11450 Blocked By: | Blocking: Related Tickets: #11449, #11451 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * milestone: 8.0.2 => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11450#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11450: Associated types at wrong type in instance
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: closed
Priority: high | Milestone: 8.2.1
Component: Compiler | Version: 7.10.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC accepts | Test Case: indexed-
invalid program | types/should_fail/T11450
Blocked By: | Blocking:
Related Tickets: #11449, #11451 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott
participants (1)
-
GHC