ghc 7.6.1 panic, http://hackage.haskell.org/trac/ghc/ticket/5252 not dead yet
Evan Laforge
qdunkan at gmail.com
Thu Sep 13 07:13:00 CEST 2012
So I have something that looks similar to
http://hackage.haskell.org/trac/ghc/ticket/5252, namely, given these
two modules:
% cat Midi.hs
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Midi (
WriteMessage(..)
, WriteDevice
-- TODO due ghc bug: http://hackage.haskell.org/trac/ghc/ticket/5252
-- , WriteDevice(WriteDevice)
) where
import qualified Data.ByteString as ByteString
data WriteMessage = WriteMessage !WriteDevice
newtype WriteDevice = WriteDevice ByteString.ByteString
% cat CoreMidi.hs
module CoreMidi where
import qualified Midi
write_message :: Midi.WriteMessage -> IO Bool
write_message (Midi.WriteMessage _) = return True
% ghc -c Midi.hs
% ghc -c CoreMidi.hs
ghc: panic! (the 'impossible' happened)
(GHC version 7.6.1 for x86_64-apple-darwin):
reboxProduct: not a product main:Midi.WriteDevice{tc r2M}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Oddly, if I put {-# UNPACK #-} on the strict WriteDevice and remove
-funbox-strict-fields, I don't get a crash anymore. Also, it has to
be ByteString inside, I guess it has to do with the optimization
ByteString applies.
Shall I append to the old ticket, or create a new one?
More information about the Glasgow-haskell-users
mailing list