[GHC] #16181: ghc panic when using DerivingVia

#16181: ghc panic when using DerivingVia -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.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: -------------------------------------+------------------------------------- The following program results in a ghc panic: {{{#!hs {-# LANGUAGE DerivingVia #-} import Data.Functor.Const (Const(..)) import Data.Functor.Classes newtype FlipConst a b = FlipConst b deriving (Show1, Eq1) via (Const b) }}} Here is the output of the compile: {{{#!sh test/Spec/Contravariant.hs:52:13: error: • No instance for (Show b) arising from the 'deriving' clause of a data type declaration Possible fix: add (Show b) to the context of the deriving clause for ‘Show1 (FlipConst a)’ or use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Show1 (FlipConst a)) | 52 | deriving (Show1, Eq1) via (Const b) | ^^^^^ test/Spec/Contravariant.hs:52:13: error:ghc: panic! (the 'impossible' happened) (GHC version 8.6.3 for x86_64-unknown-linux): No skolem info: [b_a3eO] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2891:5 in ghc:TcErrors Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I'm using GHC 8.6.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16181 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16181: ghc panic when using DerivingVia -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: derivingvia 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 chessai): * keywords: => derivingvia * failure: None/Unknown => Compile-time crash or panic -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16181#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16181: ghc panic when using DerivingVia -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #15831 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: derivingvia => deriving * related: => #15831 Comment: Great test case. I have a strong hunch that this is a symptom of #15831. When I get around to fixing that, I'll check whether that fixes this ticket as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16181#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC