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

GHC ghc-devs at haskell.org
Wed Mar 8 16:04:12 UTC 2017


#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


More information about the ghc-tickets mailing list