[GHC] #15002: Panic: collectNBinders

GHC ghc-devs at haskell.org
Wed Apr 4 20:26:03 UTC 2018


#15002: Panic: collectNBinders
-------------------------------------+-------------------------------------
        Reporter:  crockeea          |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:  8.4.2
       Component:  Profiling         |              Version:  8.4.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * priority:  normal => highest
 * version:  8.4.2-rc1 => 8.4.1
 * component:  Compiler => Profiling


Comment:

 Thanks for the bug report. Note that one can also reproduce this with GHC
 8.4.1 as well.

 Here is a minimal example:

 {{{#!hs
 module Bug where

 import Control.Concurrent.MVar (MVar, modifyMVar_, putMVar)
 import Data.Foldable (for_)

 broadcastThen :: Either [MVar a] a -> MVar (Either [MVar a] a) -> a -> IO
 ()
 broadcastThen finalState mv x =
     modifyMVar_ mv $ \mx -> do
       case mx of
         Left ls -> do for_ ls (`putMVar` x)
                       return finalState
         Right _ -> return finalState
 }}}
 {{{
 $ ~/Software/ghc-8.4.1/bin/ghc -fprof-auto -prof -fforce-recomp -O1 Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.1 for x86_64-unknown-linux):
         collectNBinders
   1
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/coreSyn/CoreSyn.hs:2189:39 in
 ghc:CoreSyn
 }}}

 Note that this bug goes away if one removes the `-O1` or `-fprof-auto`
 flags.

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


More information about the ghc-tickets mailing list