[GHC] #10549: floatExpr tick break<2>
GHC
ghc-devs at haskell.org
Sat Aug 1 14:32:38 UTC 2015
#10549: floatExpr tick break<2>
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.10.3
Component: Compiler | Version: 7.10.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Changes (by thomie):
* priority: normal => high
* version: 7.11 => 7.10.2
* milestone: => 7.10.3
Comment:
Here is a test to reproduce the problem with ghci.
{{{
{-# OPTIONS_GHC -O2 #-}
module T10549 where
import qualified Data.ByteString.Internal as Internal
import System.IO.Unsafe (unsafePerformIO)
import Data.Word (Word8)
import Foreign.Ptr (Ptr)
import Foreign.Storable (peek)
type S = Ptr Word8
chr :: S -> Char
chr x = Internal.w2c $ unsafePerformIO $ peek x
}}}
Running `ghc-7.10.1 --interactive T10549.hs` results in:
{{{
GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help
T10549.hs:1:16: Warning:
-O conflicts with --interactive; -O ignored
[1 of 1] Compiling T10549 ( T10549.hs, interpreted )
Ok, modules loaded: T10549.
}}}
Running `ghc-7.10.2 --interactive T10549.hs` results in:
{{{
GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling T10549 ( T10549.hs, interpreted )
ghc: panic! (the 'impossible' happened)
(GHC version 7.10.2 for x86_64-unknown-linux):
floatExpr tick break<3>()
}}}
So somehow the `OPTIONS_GHC -O2` in the file doesn't get ignored (it does
when given on the command line).
To reproduce the problem with the Shake sources (version 0.15.4), run
`ghci src/Development/Ninja/Lexer.hs -isrc`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10549#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list