[GHC] #13393: GHC panic: No skolem info

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I got this GHC output: {{{ /home/sven/DEV_LBM/lbm-talk-flow/mediabus-fdk- aac/src/Data/MediaBus/Audio/FdkAac/Encoder.hs:124:8: error:ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): No skolem info: k_ataY[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} It happens when I omit a type signature. We do not have the resources right now to create a minimal test case, but I didn't want to ignore the request to file a bug report. This happens in a small project available on github, I commited the specific code and tagged the commit 'ghc-panic' and added a comment in the code. I doubt that is makes sense to paste the code here, so if anyone looks into this, please grab the code from github at: [https://github.com/lindenbaum/mediabus-fdk-aac/blob/ghc- panic/src/Data/MediaBus/Audio/FdkAac/Encoder.hs] Sorry if this bug report is not helpful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Perhaps this is fixed already? See #13297, #13135, #12844. Would it be possible to check? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sadly, I just tried compiling this on GHC HEAD, and the panic is still present. I need to see if I can minimize this to a reproducible test case. (Moreover, I discovered another bug in the process: #13398) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): OK, here's something with no dependencies which triggers the same panic: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} module Mediabus ( ) where import Control.Monad.Trans.RWS.Strict (RWST) import Data.Functor.Identity (Identity) import Data.Kind (Type) import Data.Word (Word16) data Rate data Audio (sampleRate :: Rate) (channelLayout :: Type) (encoding :: Type) data EncodeResult = MkEncodeResult { encodeResultLeftOverInput :: !(Maybe [Word16]) } data EncodeFailure data AacEncErrorCode data Aac (aot :: AacCodec) data AacCodec newtype AacEncSt (rate :: Rate) channels (codec :: AacCodec) = MkAacEncSt { _leftOvers :: Maybe [Word16] } -- makeLenses ''AacEncSt type Iso s t a b = forall p f. (Functor f) => (a -> f b) -> s -> (f t) instance (Monad m, Monoid w) => MonadState s (RWST r w s m) where iso :: (s -> a) -> (b -> t) -> Iso s t a b iso sa bt x = fmap bt . x . sa {-# INLINE iso #-} leftOvers :: forall rate_a750 channels_a753 codec_a757 rate_aaYK channels_aaYL codec_aaYM. Iso (AacEncSt rate_a750 channels_a753 codec_a757) (AacEncSt rate_aaYK channels_aaYL codec_aaYM) (Maybe [Word16]) (Maybe [Word16]) leftOvers = (iso (\ (MkAacEncSt x_aaYN) -> x_aaYN)) MkAacEncSt {-# INLINE leftOvers #-} type ASetter s t a b = (a -> Identity b) -> s -> Identity t class Monad m => MonadState s m | m -> s where (.=) :: MonadState s m => ASetter s s a b -> b -> m () l .= b = undefined {-# INLINE (.=) #-} type AacEncT rate channels codec m a = RWST Int () (AacEncSt rate channels codec) m a encodeLinearToAac :: AacEncT rate channels codec IO (Either EncodeFailure (Maybe (Audio rate channels (Aac codec)))) encodeLinearToAac = do mapM putBackLeftOverInputAndReturnOutput undefined undefined where putBackLeftOverInputAndReturnOutput (MkEncodeResult x) = do leftOvers .= x undefined }}} This was actually introduced in GHC 8.0.2, it seems. On GHC 8.0.1, it gives this error: {{{ Bug.hs:63:3: error: • Ambiguous type variable ‘t0’ arising from a use of ‘mapM’ prevents the constraint ‘(Traversable t0)’ from being solved. Probable fix: use a type annotation to specify what ‘t0’ should be. These potential instances exist: instance Traversable (Either a) -- Defined in ‘Data.Traversable’ instance Traversable Identity -- Defined in ‘Data.Functor.Identity’ instance Traversable Maybe -- Defined in ‘Data.Traversable’ ...plus two others ...plus 24 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In a stmt of a 'do' block: mapM putBackLeftOverInputAndReturnOutput undefined In the expression: do { mapM putBackLeftOverInputAndReturnOutput undefined; undefined } In an equation for ‘encodeLinearToAac’: encodeLinearToAac = do { mapM putBackLeftOverInputAndReturnOutput undefined; undefined } where putBackLeftOverInputAndReturnOutput (MkEncodeResult x) = do { leftOvers .= x; .... } }}} But on GHC 8.0.2, it panics: {{{ Bug.hs:63:8: error:ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): No skolem info: k_a2RY[sk] }}} So does GHC HEAD: {{{ Bug.hs:63:8: error:ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20170307 for x86_64-unknown-linux): No skolem info: k_a3pM[sk:3] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1191:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2627:5 in ghc:TcErrors }}} The presence of `PolyKinds` is crucial to triggering this bug. Without `PolyKinds`, you get the same error message on GHC 8.0.2 and HEAD as you would with 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sheyll): Wow, what an awesome response, thank you RyanGlScott -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Ha! I have a fix validating for #13371, and it seems to fix this one too! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Heh, that is a funny coincidence. I even managed to discover that the same commit that caused this regression (c9bcaf3165586ac214fa694e61c55eb45eb131ab) is also responsible for #13371. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13393: GHC panic: No skolem info
-------------------------------------+-------------------------------------
Reporter: sheyll | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13393: GHC panic: No skolem info -------------------------------------+------------------------------------- Reporter: sheyll | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: crash or panic | polykinds/T13393 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => polykinds/T13393 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13393#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC