[GHC] #14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop)

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 (Type checker) | Keywords: deriving, | Operating System: Unknown/Multiple CustomTypeErrors | Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code panics on GHC 8.2.1 and later: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE UndecidableInstances #-} module Bug where import GHC.TypeLits newtype Baz = Baz Foo deriving Bar newtype Foo = Foo Int class Bar a where bar :: a instance (TypeError (Text "Boo")) => Bar Foo where bar = undefined }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.1 for x86_64-unknown-linux): solveDerivEqns: probable loop DerivSpec ds_loc = Bug.hs:9:12-14 ds_name = $fBarBaz ds_tvs = [] ds_cls = Bar ds_tys = [Baz] ds_theta = [ThetaOrigin to_tvs = [] to_givens = [] to_wanted_origins = [Bar Foo, (Foo :: *) ~R# (Baz :: *)]] ds_mechanism = newtype [[s0_a1D7[fuv:0]]] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcDerivInfer.hs:515:9 in ghc:TcDerivInfer }}} This is a regression since GHC 8.0.2, in which it does compile successfully. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: deriving, Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This is technically my fault, since this regression first started happening in 639e702b6129f501c539b158b982ed8489e3d09c (`Refactor DeriveAnyClass's instance context inference`). That being said, I don't have any inclination as to what part of that patch tickles this panic. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: deriving, Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kosmikus): * cc: kosmikus (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns:
probable loop)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.2.1
checker) | Keywords: deriving,
Resolution: | CustomTypeErrors
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: deriving, Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | testsuite/tests/deriving/should_compile/T14339 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => testsuite/tests/deriving/should_compile/T14339 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: 8.2.3 Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: deriving, Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | testsuite/tests/deriving/should_compile/T14339 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: 8.4.1 => 8.2.3 Comment: This was marked as merge with no release target, so I'll optimistically assume you meant 8.2.3, if there is one planned. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: 8.2.2 Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: deriving, Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | testsuite/tests/deriving/should_compile/T14339 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.3 => 8.2.2 Comment: Ahh, good catch RyanGlScott. Actually I think we can sneak it in to 8.2.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14339: GHC 8.2.1 regression when combining GND with TypeError (solveDerivEqns: probable loop) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.2.2 Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: deriving, Resolution: fixed | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | testsuite/tests/deriving/should_compile/T14339 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in a05d71a73048df005c924f023607005a327e2adf. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14339#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC