[GHC] #14266: AllowAmbiguousTypes doesn't play well with default class methods

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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: -------------------------------------+------------------------------------- This example does compile, {{{ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-} class A t where f :: forall x m. Monoid x => t m -> m f = undefined instance A [] where f = undefined }}} and it seems that the following really ought to be equivalent to it, since all I have done is remove a method definition which is identical to the default: {{{ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-} class A t where f :: forall x m. Monoid x => t m -> m f = undefined instance A [] }}} But instead GHC 8.0.2 gives an error of "Could not deduce (Monoid x0)" on the instance declaration. (I've also posed the same question on stackoverflow: https://stackoverflow.com/q/46350839/402884.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 chris-martin: Old description:
This example does compile,
{{{ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-}
class A t where f :: forall x m. Monoid x => t m -> m f = undefined
instance A [] where f = undefined }}}
and it seems that the following really ought to be equivalent to it, since all I have done is remove a method definition which is identical to the default:
{{{ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-}
class A t where f :: forall x m. Monoid x => t m -> m f = undefined
instance A [] }}}
But instead GHC 8.0.2 gives an error of "Could not deduce (Monoid x0)" on the instance declaration.
(I've also posed the same question on stackoverflow: https://stackoverflow.com/q/46350839/402884.)
New description: This example does compile, {{{ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-} class A t where f :: forall x m. Monoid x => t m -> m f = undefined instance A [] where f = undefined }}} and it seems that the following really ought to be equivalent to it, since all I have done is remove a method definition which is identical to the default: {{{ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-} class A t where f :: forall x m. Monoid x => t m -> m f = undefined instance A [] }}} But instead GHC 8.0.2 gives an error of "Could not deduce (Monoid x0)" on the instance declaration. (I've also first posed this as a question on stackoverflow: https://stackoverflow.com/q/46350839/402884.) -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 RyanGlScott): * cc: RyanGlScott (added) Comment: I can at least explain why you're seeing that error. GHC doesn't typecheck default methods by inlining their bodies like you suggest. Instead, it defines an auxiliary method and defines default `f` implementations in terms of that, like so: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE TypeApplications #-} class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f = df @[] df :: forall t. A t => forall x m. Monoid x => t m -> m df = undefined }}} You'll get the same sort of error from this code as well: {{{ GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:9:7: error: • Could not deduce (Monoid x0) arising from a use of ‘df’ from the context: Monoid x bound by the type signature for: f :: forall x m. Monoid x => [m] -> m at Bug.hs:9:3 The type variable ‘x0’ is ambiguous These potential instances exist: instance Monoid a => Monoid (IO a) -- Defined in ‘GHC.Base’ instance Monoid Ordering -- Defined in ‘GHC.Base’ instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’ ...plus 7 others (use -fprint-potential-instances to see them all) • In the expression: df @[] In an equation for ‘f’: f = df @[] In the instance declaration for ‘A []’ | 9 | f = df @[] | ^^^^^^ }}} As for how one would change this code to make this typecheck, I'm not sure. At first, I thought one could solve this by simply applying more arguments via `TypeApplications`, like so: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f :: forall x m. Monoid x => [m] -> m f = df @[] @x @m df :: forall t. A t => forall x m. Monoid x => t m -> m df = undefined }}} But this just shifts the location of the error around: {{{ GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:10:8: error: • Could not deduce (Monoid x0) from the context: Monoid x bound by the type signature for: f :: forall x m. Monoid x => [m] -> m at Bug.hs:10:8-39 The type variable ‘x0’ is ambiguous • When checking that instance signature for ‘f’ is more general than its signature in the class Instance sig: forall x m. Monoid x => [m] -> m Class sig: forall x m. Monoid x => [m] -> m In the instance declaration for ‘A []’ | 10 | f :: forall x m. Monoid x => [m] -> m | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} This is all despite the fact that you can redefine `f` as a top-level function, and it works! {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f = undefined f' :: forall x m. Monoid x => [m] -> m f' = df @[] @x @m df :: forall t. A t => forall x m. Monoid x => t m -> m df = undefined }}} It's all quite confusing. I find myself very unclear of when exactly `AllowAmbiguousTypes` is supposed to kick in and save me from ambiguity errors (because in the case of class methods, it's clearly not). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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): Several things to say here. First, the signature for `f` is deeply suspicious {{{ class A t where f :: forall x m. Monoid x => t m -> m }}} Any call of `f` will require a `Monoid x` constraint, but does not fix `x` in any way. So all calls will be ambiguous unless you use visible type application. Second, Ryan's account of what GHC does with default methods is absolutely right. Third, yes, it is a bit awarkard that there doesn't seem to be a way to make this (very odd) program "work". Ryan tried visible type application: {{{ instance A [] where f :: forall x m. Monoid x => [m] -> m f = df @[] @x @m }}} But when you write a type signature in an instance declaration, you are free to make it more genreal than the one required. For example: {{{ instance Num Wombat where (+) :: forall a b. a -> b -> a (+) x y = x }}} We are obliged to provide a function of type `Wombat -> Wombat -> Wombat`, but we are perfectly free to provide a more polymorphic one. Equivalently you could write {{{ instance Num Wombat where (+) = (\x y -> x) :: forall a b. a -> b -> a }}} So GHC still has to check that the type you have supplied is more polymorphic than the one required and alas in ''that'' test you can't do visible type application. That's why Ryan found that "this just shifts the error around". (And it also explains why the "top-level function" version is ok. It was a surprise to me that I can see no way to allow to write an instance when the method has a a locally-polymorphic but ambiguous method types. If there was a good reason to want them, maybe we should think about it more. If it's just a curiousity, then it's just curious. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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:3 simonpj]:
If there was a good reason to want them, maybe we should think about it more.
I'm not chris-martin, but I do have an example of actual code he was trying to write that tickled this bug. This is what he wanted to write: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module MultiInstance where class MultiMonoid x a where multi'append :: a -> a -> a multi'empty :: a data Addition data Multiplication instance MultiMonoid Addition Int where multi'append = (+) multi'empty = 0 instance MultiMonoid Multiplication Int where multi'append = (*) multi'empty = 1 example1, example2 :: Int example1 = multi'append @Addition 2 3 -- 5 example2 = multi'append @Multiplication 2 3 -- 6 class MultiFoldable t where multi'foldMap :: forall x m a. (MultiMonoid x m) => (a -> m) -> t a -> m instance MultiFoldable [] where multi'foldMap :: forall x m a. (MultiMonoid x m) => (a -> m) -> [a] -> m multi'foldMap f = go where go :: [a] -> m go [] = multi'empty @x go (x:xs) = multi'append @x (f x) (go xs) example3, example4 :: Int example3 = multi'foldMap @[] @Addition id [1,2,3,4] -- 10 example4 = multi'foldMap @[] @Multiplication id [1,2,3,4] -- 24 }}} To explain what's going on here: `MultiMonoid` is a class where the first parameter determines what sort of `Monoid` you're working on over the second parameter, so `multi'append @Addition` uses `{(+), 0}` as the `Monoid`, and `multi'append @Multiplication` uses `{(*), 1}` as the `Monoid`. So far, nothing about this requires `AllowAmbiguousTypes`. Now we enter `MultiFoldable`. This class only has one parameter, but its method `multi'foldMap` has a given `MultiMonoid x m` constraint. Here, `x` is ambiguous, so this crucially relies on `AllowAmbiguousTypes` working. Some demonstrations of `multi'foldMap`'s use are found in `example3` and `example4`. This fails to compile: {{{ Bug.hs:32:22: error: • Could not deduce (MultiMonoid x0 m) from the context: MultiMonoid x m bound by the type signature for: multi'foldMap :: forall x m a. MultiMonoid x m => (a -> m) -> [a] -> m at Bug.hs:32:22-76 The type variable ‘x0’ is ambiguous • When checking that instance signature for ‘multi'foldMap’ is more general than its signature in the class Instance sig: forall x m a. MultiMonoid x m => (a -> m) -> [a] -> m Class sig: forall x m a. MultiMonoid x m => (a -> m) -> [a] -> m In the instance declaration for ‘MultiFoldable []’ | 32 | multi'foldMap :: forall x m a. (MultiMonoid x m) => (a -> m) -> [a] -> m | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 chris-martin): Thanks Ryan - yes that's a great description of what I was trying to do. One correction: I'm pretty sure `MultiMonoid` alone ''does'' require `AllowAmbiguousTypes` even before you get to `MultiFoldable`. The "complete" result is now on Hackage https://hackage.haskell.org/package/multi- instance-0.0.0.1/docs/MultiInstance.html although I ended up scrapping the `MultiFoldable` class altogether. It was an extended thought experiment more than anything, probably beyond the bounds of reasonable Haskell. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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:5 chris-martin]:
Thanks Ryan - yes that's a great description of what I was trying to do. One correction: I'm pretty sure `MultiMonoid` alone ''does'' require `AllowAmbiguousTypes` even before you get to `MultiFoldable`.
Ah, good point. I suppose the distinction I was making in the back of my mind was that in `MultiMonoid`, the ambiguity comes from a type variable from the //class//, whereas in `MultiFoldable`, the ambiguity comes from a type variable from a //method// (`multi'foldMap`). I believe the former can coexist with `DefaultSignatures`, whereas the latter cannot (as this bug demonstrates).
It was an extended thought experiment more than anything, probably beyond the bounds of reasonable Haskell.
I think you're selling your idea short! The only reason this code would have been considered unreasonable in the past is due to the lack of `TypeApplications`, but now that it's an established thing, the scope of what's considered "reasonable" code has increased drastically. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 chris-martin): Replying to [comment:6 RyanGlScott]:
but now that it's an established thing, the scope of what's considered "reasonable" code has increased drastically.
I suppose that's something I'm not clear on. What is the language designers' attitude toward the `TypeApplications` extension? Is it there to be an imperfect workaround for the occasional odd situation, or is Haskell now intended to be a language where programming with ambiguous types is normal and fully supported? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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:7 chris-martin]:
I suppose that's something I'm not clear on. What is the language designers' attitude toward the `TypeApplications` extension? Is it there to be an imperfect workaround for the occasional odd situation, or is Haskell now intended to be a language where programming with ambiguous types and explicit type applications is normal and fully supported? It still //feels// a bit like I'm abusing the type system.
I can only speak as a single GHC developer, but I would certainly hope that `TypeApplications` is just as "fully supported" as anything else you can do in GHC (and I suspect I'm not alone in this regard). The somewhat unfortunate reality is that this extension is fairly new in the Haskell ecosystem, and as a result, there's been less time to discover odd interactions between it and other language extensions (of which this bug is an example). With the help of intrepid programmers like yourself, I think we'll find a way to stamp out these oddities, and hopefully make `TypeApplications` feel less like "abusing" the type system. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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): As the author of `TypeApplications`, I have greatly enjoyed its quick adoption in a variety of places. It's a stable extension based on published theory. I, personally, do not consider it a "workaround" at all and think it's a fine extension to build on. It ''is'' a little sketchy around the corners, however. Ryan has been working on making it work better with GADTs, and we still need support for types in patterns. That said, any place where `TypeApplications` works today will continue to work tomorrow, and I think you can use it without fear. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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): Here's my problem. Consider {{{ class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f :: forall m x. Semigroup x => [m] -> m f = blah }}} (Reminder: `SemiGroup` is a superclass of `Monoid`.) Assume that `blah` really only uses `SemiGroup`. So in this instance declaration the definition of `f`, and its type signature, are strictly more general than the ones required. Just for fun I put the type arguments in a different order. So this should typecheck. But there is some real impedance matching to do. If I write it out with explicit type and dictionary applications it might be like this {{{ inst_f :: forall m x. Semigroup x => [m] -> m inst_f = /\ m x. \(ds:SemiGroup x). blah<mentions ds> instance A [] where f = /\ x m. \(dm:Monoid x). inst_f @m @x (sc_select dm) }}} Here `inst_f` is the function as declared by the user in the instance decl. The code in the instance decl itself I have to swizzle the type arguments, and do a superclass selection on the dictionary argument before calling `inst_f`. So there is work to do! GHC has to work out how to get a `[W] SemiGroup x0` from a `[G] Monoid x`, where `x0` is unification variable. A good guess is to set `x0 := x` but GHC's solver doesn't guess. Do you see the problem? But the programmer says "I wasn't doing any of this more-general-type nonsense. I wrote down precisely the instantiated type so it's ''obvious'' how to match things up". And that seems like a reasonable observation. I suppose that we could say that when the instantiated method type ''precisely matches'' the user-specified signature, then we just match things up in the obvious way. That seems like a very ''ad hoc'' hack. But I can't see any other way. Any other ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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'm a bit lost here. Your "reduced" example seems to be asking a lot more out of GHC than what the original example demands! That is, the original example is simply: {{{#!hs class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f :: forall x m. Monoid x => [m] -> m f = blah }}} No superclass relationships. No argument swizzling. I'd be content with just this, since that's all that `DefaultSignatures` needs! Does that make the problem easier? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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):
I'd be content with just this,
That's what I was suggesting when I said "I suppose that we could say that when the instantiated method type precisely matches the user-specified signature, then we just match things up in the obvious way." But GHC currently does the more general thing which, I bet, someone someday will report as a bug if we insist on a precise match. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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'm incredibly confused. We seem to be talking about two different issues here: * The fact that `InstanceSigs`' "more-general-than" check gets confused when `AllowAmbiguousTypes` comes into play. That is indeed a perplexing issue, and I can't offer a suggestion on how to fix it. But it's a distraction, since I was only using `InstanceSigs` to motivate the original issue, which is... * `DefaultSignatures` gets confused when interacting with `AllowAmbiguousTypes`. We needn't bother with any sort of "more-general- than" check here, because `DefaultSignatures` emits code that doesn't use any instance signatures, right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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): Its nothing to do with `AllowAmbiguousTypes`, except that the latter is needed to allow you to write the signature at all. What I wrote all happens after the signature is accepted.
because DefaultSignatures emits code that doesn't use any instance signatures, right
I don't understand that. Your example made essential use of instance signatures. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 thoroughly regret ever mentioning `InstanceSigs`, because that has nothing to do with the underlying issue here, and it has completely derailed the discussion. Here is the code that should compile, but doesn't (from comment:2): {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE TypeApplications #-} class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f = df @[] df :: forall t. A t => forall x m. Monoid x => t m -> m df = undefined }}} This is precisely what gets emitted with `DefaultSignatures` (module naming). No `InstanceSigs` to be found. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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've been only loosely following along. But comment:15 has a very clear "here is the code that should compile". And so I tried it. And it doesn't. But of course it doesn't, as `df` has no way of knowing that the `Monoid x` instance in scope in the instance definition for `f` is the one to use. To bring the type variable `x` into scope, it's necessary to use `InstanceSigs` so that you can write a type signature bringing `x` into scope. (By the way, if you use an expression type signature, the problem is no better.) What I argue should compile is this: {{{#!hs class A t where f :: forall x m. Monoid x => t m -> m instance A [] where f :: forall x m. Monoid x => [m] -> m f = df @[] @x df :: forall t. A t => forall x m. Monoid x => t m -> m df = undefined }}} But this, too, doesn't compile because of the "more-general-than" check in `InstanceSigs`, which can't be informed about what to do for `x`. While I don't see any technical complications with allowing the user to direct the "more-general-than" check, I can't think of any concrete syntax that isn't nightmarish. Perhaps we're simply barking up the wrong tree here, though. Suppose I could write {{{#!hs instance A [] where f @x = df @[] @x }}} where `f @x` is a visible type pattern. That would bring the right `x` into scope (no `InstanceSigs`!) And then the "more-general-than" comparison is not needed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 like Richard's visible type pattern suggestion far more than trying to fiddle with `InstanceSigs`. (Well, except for the fact that we don't currently have visible type patterns. But I'll try not to be impatient.) If we do go down this route, I suppose we'd need to eta-expand //all// arguments of a default function when desugaring `DefaultSignatures` so that something like this would work: {{{#!hs class A t where f :: forall m. t m -> forall x. Monoid x -> m instance A [] where f @m tm @x = df @[] @m tm @x }}} Since I believe we'd need to visibly apply `@x` there in order to avoid being ensnared in ambiguity. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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): Re comment:15; ah yes, I see, thanks. I was writing in response to comment:4. However, note that * All I wrote in comment:10 applies regardless of any stuff to do with type patterns. If you write an instance sig, it needs to be matched up with the class decl. * If you ''do'' write an instance sig, then the difficulties of comment:15 can be dealt with by emitting a suitable instance sig, which in turn supports visible type application. So I still say that comment:10 describes the number-1 problem. Yes, type patterns might be nice too. The last para of comment:10 describes a solution that might be workable -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 glaebhoerl): * cc: glaebhoerl (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14266#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC