[GHC] #15443: ghc panic when running GI.init on intero REPL

GHC ghc-devs at haskell.org
Fri Jul 27 09:58:14 UTC 2018


#15443: ghc panic when running GI.init on intero REPL
--------------------------------+--------------------------------------
        Reporter:  esclerofilo  |                Owner:  (none)
            Type:  bug          |               Status:  new
        Priority:  normal       |            Milestone:  8.6.1
       Component:  GHCi         |              Version:  8.4.3
      Resolution:               |             Keywords:
Operating System:  Linux        |         Architecture:  x86_64 (amd64)
 Type of failure:  GHCi crash   |            Test Case:
      Blocked By:               |             Blocking:
 Related Tickets:               |  Differential Rev(s):
       Wiki Page:               |
--------------------------------+--------------------------------------

Comment (by mr.schyte):

 Hi! I've hit the same bug with intero. If I try calling a function from
 the emacs repl I receive the panic message, but the same call works fine
 from the terminal.
 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.3 for x86_64-unknown-linux):
         nameModule
   system $dShow_a4FZ
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/basicTypes/Name.hs:241:3 in ghc:Name

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

 This is the program I'm using; I'm trying to call "readBlock s 10", which
 fails. I can call both blockPath and print blocks using show without
 errors.
 {{{
 module Lib
   where

 import Control.Exception (try, catch, IOException)
 import qualified Data.ByteString as B
 import System.FilePath
 import Text.Printf (printf)

 data Block = Block {
   offset :: Int, -- Padding length at the front
   bytes :: B.ByteString -- The contents of the block
 } deriving Show

 data Store = Store {
   dirs :: [FilePath],
   bsize :: Int,
   count :: Int
 }

 s = Store ["/tmp/1", "/tmp/2"] 10 10

 blockPath :: Store -> Int -> FilePath
 blockPath (Store d _ _) i = dir </> (printf "%016x.dat" i)
   where
     dir = d !! (mod i (length d))

 readBlock :: Store -> Int -> IO (Block)
 readBlock s i = catch (B.readFile path >>= (return . (Block i))) handler
   where
     handler :: IOException -> IO (Block)
     handler _ = return $ Block 0 (B.replicate (bsize s) 0)
     path = blockPath s i
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15443#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list