[GHC] #12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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: -------------------------------------+------------------------------------- This code compiles without issue on GHC 8.0.1 and earlier, but not with GHC 8.0.2 or HEAD. This was adapted from the [https://github.com/kazu- yamamoto/logger/blob/master/monad-logger/Control/Monad/Logger.hs monad- logger] library (which fails to build with GHC 8.0.2 and HEAD due to the same issue): {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} module MonadLogger where import Control.Monad.IO.Class import qualified Control.Monad.Trans.Class as Trans import Control.Monad.Trans.Identity data Loc data LogSource data LogLevel data LogStr class ToLogStr msg class Monad m => MonadLogger m class (MonadLogger m, MonadIO m) => MonadLoggerIO m where askLoggerIO :: m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) default askLoggerIO :: (Trans.MonadTrans t, MonadLogger (t m), MonadIO (t m)) => t m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) askLoggerIO = Trans.lift askLoggerIO instance MonadLogger m => MonadLogger (IdentityT m) instance MonadLoggerIO m => MonadLoggerIO (IdentityT m) }}} On GHC HEAD, this fails with: {{{ [1 of 1] Compiling MonadLogger ( MonadLogger.hs, interpreted ) MonadLogger.hs:23:10: error: • Couldn't match type ‘m’ with ‘IdentityT m’ ‘m’ is a rigid type variable bound by the instance declaration at MonadLogger.hs:23:10-55 Expected type: IdentityT m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) Actual type: IdentityT (IdentityT m) (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) • In the expression: MonadLogger.$dmaskLoggerIO @IdentityT m In an equation for ‘askLoggerIO’: askLoggerIO = MonadLogger.$dmaskLoggerIO @IdentityT m In the instance declaration for ‘MonadLoggerIO (IdentityT m)’ • Relevant bindings include askLoggerIO :: IdentityT m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) (bound at MonadLogger.hs:23:10) }}} This stopped typechecking after d2958bd08a049b61941f078e51809c7e63bc3354 (i.e, #12220). As a workaround, you can change the default signature to: {{{#!hs default askLoggerIO :: (Trans.MonadTrans t, MonadLoggerIO n, t n ~ m) => t n (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) }}} And it'll work. Any thoughts on this, Simon? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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 snoyberg): * cc: snoyberg (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): I don't know exactly what changed in GHC here, but the current monad- logger code is utterly wrong and the "workaround" is actually just replacing the code with what the author doubtless meant to write in the first place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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 RyanGlScott): * cc: bgamari (added) Comment: rwbarton, if I understand correctly, the issue here is that we're trying to equate `t m` with `m`? (It sort of looks like a variation of the occurs check, but I don't know if it's the same thing, given the nature of the error message.) It certainly seems like this program shouldn't have typechecked before, and that's fine. But the other issue is that we have a program which compiles on 8.0.1 but fails with 8.0.2, which seems a bit iffy. (See also https://ghc.haskell.org/trac/ghc/ticket/12768#comment:5 for another example.) Should we avoid backporting this fix to 8.0.2 to give users time to migrate their code that exhibits this bug before the next major release (8.2) lands? Or should we just pull the trigger and add a blurb to the 8.0.2 release notes explaining the situation? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): I just mean to say that `monad-logger` should just fix its code, since the fix will surely be needed anyway. RyanGlScott, it's more wrong than that. Let's charitably assume that `t m` refers to the instance we are deriving, like `IdentityT m`. Then how can the body of the default declaration type check? {{{#!hs askLoggerIO = Trans.lift askLoggerIO }}} `askLoggerIO` is a method of `MonadLoggerIO` and we need it at type `m`. But we only have the constraints `MonadLogger (t m), MonadIO (t m)`, which are insufficient (and useless). The only way GHC could think this type checks is if BOTH `t m` and `m` refer to the instance being derived, which is terribly wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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 RyanGlScott): Wow, those constraints are really off! To highlight how bad the behavior was in 8.0.1, even this typechecks! {{{#!hs class (MonadLogger m, MonadIO m) => MonadLoggerIO m where askLoggerIO :: m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) default askLoggerIO :: (Trans.MonadTrans t) => t m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) askLoggerIO = Trans.lift askLoggerIO }}} I'll draft up a patch for the 8.0.2 users' guide explaining this difference the a similar vein as ead83db8a7db772a9f248af9767a4283218a5c9f. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2682 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The change in behavior is surely a bug fix here. Changes in user-facing behavior between minor versions due to bug fixing are OK. And I agree with Ryan's phrasing in the Phab Diff. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.0.2
Component: Compiler | Version: 8.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): Phab:D2682
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge Comment: Let's merge this release-notes fix into 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ilovezfs): Here's another instance in the wild that just got released: https://github.com/purescript/purescript/issues/2421. {{{ src/Control/Monad/Supply/Class.hs:30:10: error: • Couldn't match type ‘m’ with ‘StateT s m’ ‘m’ is a rigid type variable bound by the instance declaration at src/Control/Monad/Supply/Class.hs:30:10 Expected type: StateT s m Integer Actual type: StateT s (StateT s m) Integer etc. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): And the relevant code (excerpted from https://github.com/purescript/purescript/blob/master/src/Control/Monad/Suppl...): {{{#!hs class Monad m => MonadSupply m where fresh :: m Integer peek :: m Integer default fresh :: MonadTrans t => t m Integer fresh = lift fresh default peek :: MonadTrans t => t m Integer peek = lift peek instance MonadSupply m => MonadSupply (StateT s m) instance (Monoid w, MonadSupply m) => MonadSupply (WriterT w m) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 2591a4b94903d4f9d9348a92599a74aacf5eda66. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Agda also apparently exhibits an example of this, http://dpaste.com/2BQ0X7F.txt. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ack, this bug keeps creeping up in unexpected places. Well, since I'm in a bug-fixing mood, let's just patch Agda: https://github.com/agda/agda/pull/2310 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * resolution: fixed => Comment: This keeps bugging me. Is this ok or not? {{{ class Monad m => MonadSupply m where fresh :: m Integer default fresh :: MonadTrans t => t m Integer fresh = lift fresh }}} It's accepted right now. But I think it should not be; specifically, '''I think the type of the default method should differ from the main method only in its context'''. Thus if {{{ fresh :: C => blah }}} then the default method should look like {{{ default fresh :: C' => blah }}} with the same `blah`. So we should write {{{ class Monad m => MonadSupply m where fresh :: m Integer default fresh :: (MonadTrans t, MonadSupply m', m ~ t m') => m Integer -- NB: same 'm Integer' after the '=>' fresh = lift fresh }}} Why? Several reasons: * It would make no sense at all to have a type that was actually ''incompatible'' with the main method type, e.g. {{{ default fresh :: m Bool }}} That would ''always'' fail in an instance decl. * We use Visible Type Application to instantiate the default method in an instance, for reasons discussed in `Note [Default methods in instances]` in `TcInstDcls`. So we need to know exactly what the universally quantified type variables are, and when instantaited that way the type of the default method must match the expected type. With this change, the patches to Agda in comment:14 would all be signalled at the ''class'' decl, which is the right place, not the instance decl. The patches to Agda would still be needed, of course. Does that rule make sense to everyone? The [http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html #class-default-signatures user manual] is silent on what rules the default signature should obey. It's just formalising the idea that the default signature should match the main one, but perhaps with some additional constraints. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Simon, that sounds sensible to me. I was quite shocked myself to learn how many `DefaultSignatures` validity checks are shunted off until the site of instance declarations instead of the class declaration, and moreover, that there is no requirement that the normal type signature and the default type signature must be the same (modulo context differences). Of course, that all sounds wonderful in my head, but if tracking down these kinds of regressions have taught me anything, it's that fiddling with `DefaultSignatures` further is inevitably bound to break more code in the wild. I don't say that to discourage you from pursuing this change (which I think is a net positive), but be aware that there are probably Haskell programs that are abusing `DefaultSignatures` in wildly creative ways, so we'll likely step on their toes in some way. '''tl;dr''' If we change the typechecking rules for `DefaultSignatures` further, we should carefully consider whether it's worth introducing in a minor release :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Oh yes, any further change can be in 8.2. I'll proceed as I propose unless someone yells. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I like that your proposal is clear on the status of a program like {{{ class Monad m => MonadSupply m where fresh :: m Integer default fresh :: (Monad n, MonadTrans t) => t n Integer -- NB: not m fresh = lift fresh }}} which does seem like a reasonable attempt at writing a correct default signature. But it's not obvious how to type check in the presence of what amount to two type signatures for the same declaration. On the other hand, it's mildly unsatisfactory that in order to write your recommended version, you need to enable another language extension that in turn enables `MonoLocalBinds` by default, which can affect unrelated declarations in the module. It feels like the use of type equalities here is fairly mild and shouldn't logically entail the need for reasoning about local type equalities in pattern matches and so on. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): +1 to comment:15 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.0.2 => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Perhaps we should open a separate ticket for this? I think the plan in https://ghc.haskell.org/trac/ghc/ticket/12784#comment:15 goes beyond the original scope of this ticket, which was to identify a regression between 8.0.1 and 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.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): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Perhaps we should open a separate ticket for this?
Yes, please do! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed * related: => #12918 Comment: I've opened #12918 for this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): By the way it seems I was pretty far off in my estimation of how frequent this pattern is in user code (it even showed up on StackOverflow); RyanGlScott if you want to add some minimal example of this issue to the release notes I'd be in favor of that after all. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => new * resolution: fixed => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682, Wiki Page: | Phab:D2786 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: Phab:D2682 => Phab:D2682, Phab:D2786 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #12918 | Differential Rev(s): Phab:D2682,
Wiki Page: | Phab:D2786
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682, Wiki Page: | Phab:D2786 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682, Wiki Page: | Phab:D2786 -------------------------------------+------------------------------------- Changes (by kosmikus): * cc: kosmikus (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682, Wiki Page: | Phab:D2786 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * version: 8.1 => 8.0.2-rc1 * milestone: 8.2.1 => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12784: Typechecker regression in GHC 8.0.2 involving DefaultSignatures -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Phab:D2682, Wiki Page: | Phab:D2786 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in dae769049f67fdc3aff92cb828206d4c68faa2cf. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12784#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC