[GHC] #11291: DfltProb1(optasm): panic CoreToStg.myCollectArgs
GHC
ghc-devs at haskell.org
Tue Dec 29 19:58:41 UTC 2015
#11291: DfltProb1(optasm): panic CoreToStg.myCollectArgs
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
(CodeGen) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Compile-time | Test Case:
crash | typecheck/should_compile/DfltProb1
| (optasm)
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by bgamari):
* failure: None/Unknown => Compile-time crash
* component: Compiler => Compiler (CodeGen)
Old description:
> The program looks like this:
> {{{
> module DfltProb1 where
>
> import Control.Monad.ST
> import Prelude hiding (traverse)
>
> traverse :: a -> ST s [a]
> traverse = undefined
>
> -- WORKS with signature test :: Num a => [a]
> test = runST (traverse 1)
>
> main = print test
> }}}
>
> This is the failure:
> {{{
> $ ghc-7.11.20151225 -O DfltProb1.hs
> ghc-stage2: panic! (the 'impossible' happened)
> (GHC version 7.11.20151224 for x86_64-unknown-linux):
> CoreToStg.myCollectArgs
> (case traverse of _ [Occ=Dead] { }) realWorld#
> }}}
New description:
The program looks like this:
{{{#!hs
module DfltProb1 where
import Control.Monad.ST
import Prelude hiding (traverse)
traverse :: a -> ST s [a]
traverse = undefined
-- WORKS with signature test :: Num a => [a]
test = runST (traverse 1)
main = print test
}}}
This is the failure:
{{{
$ ghc-7.11.20151225 -O DfltProb1.hs
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 7.11.20151224 for x86_64-unknown-linux):
CoreToStg.myCollectArgs
(case traverse of _ [Occ=Dead] { }) realWorld#
}}}
--
Comment:
I believe this is fixed on `master`. I have a suspicion that this is due
to d990354473239943d83ee90f8906f3737b53fe65.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11291#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list