[GHC] #9964: GHC crash with NOINLINE and weird IO stuff

GHC ghc-devs at haskell.org
Wed Jan 7 20:17:49 UTC 2015


#9964: GHC crash with NOINLINE and weird IO stuff
-------------------------------------+-------------------------------------
        Reporter:  dfeuer            |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.11
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash                              |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by dfeuer:

Old description:

> {{{#!hs
> {-# LANGUAGE UnboxedTuples #-}
> module Crash where
>
> import GHC.Base
>
> crash :: IO Int
> crash = IO (\s ->
>   let
>     {-# NOINLINE s' #-}
>     s' = s
>   in (# s', 1::Int #))
> }}}
>
> This compiles under 7.6.3, but both 7.8.3 and head choke:
>
> {{{
> ghc: panic! (the 'impossible' happened)
>   (GHC version 7.8.3 for x86_64-unknown-linux):
>         StgCmmEnv: variable not found
>     s{v sLw} [lid]
>     local binds for:
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
> }}}

New description:

 {{{#!hs
 {-# LANGUAGE UnboxedTuples #-}
 module Crash where

 import GHC.Base

 crash :: IO ()
 crash = IO (\s ->
   let
     {-# NOINLINE s' #-}
     s' = s
   in (# s', () #))
 }}}

 This compiles under 7.6.3, but both 7.8.3 and head choke:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.8.3 for x86_64-unknown-linux):
         StgCmmEnv: variable not found
     s{v sLw} [lid]
     local binds for:

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

--

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


More information about the ghc-tickets mailing list