[GHC] #11232: Panic whilst compiling syb due to OptCoercion
GHC
ghc-devs at haskell.org
Tue Dec 15 17:20:59 UTC 2015
#11232: Panic whilst compiling syb due to OptCoercion
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 7.10.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Here is the minimised test case with most definitions inlined.
{{{
module Data.Generics.Aliases where
import Control.Monad
import Data.Data
mkMp :: ( MonadPlus m
, Typeable a
, Typeable b
)
=> (b -> m b)
-> a
-> m a
mkMp ext = unM (maybe (M (const mzero)) id (gcast (M ext)))
newtype M m x = M { unM :: x -> m x }
}}}
Panics with `-O2` as follows,
{{{
~/Documents/haskell/syb-0.6:ghc-7.11.20151214 Aliases.hs -O2
[1 of 1] Compiling Data.Generics.Aliases ( Aliases.hs, Aliases.o )
ghc: panic! (the 'impossible' happened)
(GHC version 7.11.20151214 for x86_64-apple-darwin):
ASSERT failed! file compiler/types/OptCoercion.hs, line 234
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11232>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list