
#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