Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,393
    • Issues 4,393
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 379
    • Merge Requests 379
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #14628

Closed
Open
Opened Jan 02, 2018 by Andreas Klebinger@AndreasKDeveloper

Panic (No skolem Info) in GHCi

Loading the following code in GHCi causes a panic.

Versions affected at least 8.2.2 and 8.0.2

module Main where

import System.IO
import Control.Monad.IO.Class
import Control.Monad.Trans.State
import Text.Printf

putArrayBytes :: Handle       -- ^ output file handle
              -> [String]     -- ^ byte-strings
              -> IO Int -- ^ total number of bytes written
putArrayBytes outfile xs = do
  let writeCount x = modify' (+ length x) >> liftIO (putLine x) :: MonadIO m => StateT Int m ()
  execStateT (mapM_ writeCount xs) 0
  where putLine = hPutStrLn outfile . ("  "++) . concatMap (printf "0x%02X,")

{-
ghci:
:break 12 46
:trace putArrayBytes stdout [['1'..'9'],['2'..'8'],['3'..'7']]
snd $ runStateT _result 0
-}

main = undefined
Configuring GHCi with the following packages:
GHCi, version 8.2.2: http://www.haskell.org/ghc/  :? for help
[1 of 1] Compiling Main             ( C:\test\test.hs, interpreted )
Ok, one module loaded.
Loaded GHCi configuration from C:\Users\Andi\AppData\Local\Temp\ghci34988\ghci-script
*Main> :break 12 46
Breakpoint 0 activated at C:\test\test.hs:12:46-63
*Main> :trace putArrayBytes stdout [['1'..'9'],['2'..'8'],['3'..'7']]
Stopped in Main.putArrayBytes.writeCount, C:\test\test.hs:12:46-63
_result :: StateT Int m () = _
putLine :: [Char] -> IO () = _
x :: [Char] = "123456789"
[C:\test\test.hs:12:46-63] [C:\test\test.hs:12:46-63] *Main> snd $ runStateT _result 0

<interactive>:3:7: error:<interactive>: panic! (the 'impossible' happened)
  (GHC version 8.2.2 for x86_64-unknown-mingw32):
        No skolem info:
  m_I5Cm[rt]
  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

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

[C:\test\test.hs:12:46-63] [C:\test\test.hs:12:46-63] *Main> :r
[1 of 1] Compiling Main             ( C:\test\test.hs, interpreted )
Ok, one module loaded.
*Main> :break 12 46
Breakpoint 1 activated at C:\test\test.hs:12:46-63
*Main> :trace putArrayBytes stdout [['1'..'9'],['2'..'8'],['3'..'7']]
Stopped in Main.putArrayBytes.writeCount, C:\test\test.hs:12:46-63
_result :: StateT Int m () = _
putLine :: [Char] -> IO () = _
x :: [Char] = "123456789"
[C:\test\test.hs:12:46-63] [C:\test\test.hs:12:46-63] *Main> snd $ runStateT _result 0

<interactive>:7:7: error:<interactive>: panic! (the 'impossible' happened)
  (GHC version 8.2.2 for x86_64-unknown-mingw32):
        No skolem info:
  m_I5Nz[rt]
  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

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

[C:\test\test.hs:12:46-63] [C:\test\test.hs:12:46-63] *Main>

Maybe related to #13393 (closed).

Trac metadata
Trac field Value
Version 8.2.2
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component GHCi
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Assignee
Assign to
None
Milestone
None
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#14628