[GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic

#14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: deriving | 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: -------------------------------------+------------------------------------- This program panics: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Bug where import Control.Concurrent (ThreadId) import Control.Monad.Reader class Wrapped s where type Unwrapped s :: * _Wrapped' :: Iso' s (Unwrapped s) type Iso' s a = forall f. Functor f => (a -> f a) -> s -> f s class Fork m where fork :: x -> m () -> m ThreadId default fork :: ( Wrapped (m ()) , Unwrapped (m ()) ~ t () , Fork t , Wrapped (m ThreadId) , Unwrapped (m ThreadId) ~ t ThreadId ) => x -> m () -> m ThreadId fork = undefined -- view _Unwrapped' . fork . view _Wrapped' instance Fork m => Fork (ReaderT e m) where fork x action = ReaderT $ \env -> fork x (runReaderT action env) data Env newtype MyThing m a = MyThing { unMyThing :: ReaderT Env m a } deriving newtype (Functor, Applicative, Monad) deriving anyclass (Fork) instance Wrapped (MyThing m a) where type Unwrapped (MyThing m a) = ReaderT Env m a _Wrapped' = undefined -- iso unMyThing MyThing }}} {{{ [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:39:24: error:ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): No skolem info: m_a1Hs[sk:2] 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/TcErrors.hs:2653:5 in ghc:TcErrors }}} (Program adapted from [https://github.com/ekmett/lens/issues/793#issuecomment-369597846 here].) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14933 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): Smaller version: {{{ {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE TypeFamilies #-} module Bug where class Wrapped s where type Unwrapped s :: * class Fork m where fork :: (x, m) default fork :: ( Wrapped m , Unwrapped m ~ t , Fork t ) => (x, m) fork = undefined newtype MyThing m = MyThing m deriving (Fork) instance Wrapped (MyThing m) where type Unwrapped (MyThing m) = m }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14933#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | 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: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4507 * related: => #14932 Comment: Ack, it turns out that we are re-using the same unification variables across multiple iterations of `simplifyDeriv`, which results in utter disaster. (Honestly, I'm not sure how anything was working before.) Phab:D4507 fixes this issue (and #14932) by generating new unification variables across //each// iteration of `simplifyDeriv`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14933#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14933: DeriveAnyClass can cause "No skolem info" GHC panic
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.2
checker) |
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: #14932 | Differential Rev(s): Phab:D4507
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14933: DeriveAnyClass can cause "No skolem info" GHC panic
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.2
checker) |
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: #14932 | Differential Rev(s): Phab:D4507
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deriving/should_compile/T14933 Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => deriving/should_compile/T14933 * milestone: => 8.4.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14933#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deriving/should_compile/T14933 Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with d8dbe2936c923471a13e214113b0e43222e95592. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14933#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC