[GHC] #13413: GHC HEAD panic: collectNBinders
GHC
ghc-devs at haskell.org
Sat Mar 11 20:12:28 UTC 2017
#13413: GHC HEAD panic: collectNBinders
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
Keywords: JoinPoints | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
`repa-eval-4.2.3.1` currently fails to build on GHC HEAD because of this
issue. Trying to build it leads to several `collectNBinders` panics is
various modules. You can reproduce this by compiling this module:
{{{#!hs
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
module Data.Repa.Eval.Generic.Seq.Chunked where
import GHC.Exts (Int#, (+#), (*#), (>=#))
-------------------------------------------------------------------------------
-- | Fill a block in a rank-2 array, sequentially.
--
-- * Blockwise filling can be more cache-efficient than linear filling
for
-- rank-2 arrays.
--
-- * The block is filled in row major order from top to bottom.
--
fillBlock2
:: (Int# -> a -> IO ()) -- ^ Update function to write into result
buffer.
-> (Int# -> Int# -> a) -- ^ Function to get the value at an (x,
y) index.
-> Int# -- ^ Width of the whole array.
-> Int# -- ^ x0 lower left corner of block to
fill.
-> Int# -- ^ y0
-> Int# -- ^ w0 width of block to fill
-> Int# -- ^ h0 height of block to fill
-> IO ()
fillBlock2
write getElem
!imageWidth !x0 !y0 !w0 h0
= do fillBlock y0 ix0
where !x1 = x0 +# w0
!y1 = y0 +# h0
!ix0 = x0 +# (y0 *# imageWidth)
{-# INLINE fillBlock #-}
fillBlock !y !ix
| 1# <- y >=# y1 = return ()
| otherwise
= do fillLine1 x0 ix
fillBlock (y +# 1#) (ix +# imageWidth)
where {-# INLINE fillLine1 #-}
fillLine1 !x !ix'
| 1# <- x >=# x1 = return ()
| otherwise
= do write ix' (getElem x y)
fillLine1 (x +# 1#) (ix' +# 1#)
{-# INLINE [0] fillBlock2 #-}
}}}
This compiles on GHC 8.0.2, but on GHC HEAD:
{{{
$ ~/Software/ghc4/inplace/bin/ghc-stage2 -fforce-recomp Bug.hs
[1 of 1] Compiling Data.Repa.Eval.Generic.Seq.Chunked ( Bug.hs, Bug.o )
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.1.20170201 for x86_64-unknown-linux):
collectNBinders
2
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1179:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1183:37 in
ghc:Outputable
pprPanic, called at compiler/coreSyn/CoreSyn.hs:1970:25 in
ghc:CoreSyn
}}}
Interestingly, compiling this triggers the panic at any optimization
level, but loading the module into GHCi does not cause it to panic.
This regression was introduced in 8d5cf8bf584fd4849917c29d82dcf46ee75dd035
(Join points).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13413>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list