
#15317: GHCi panic when trying to avoid GHC_OPTIONS -O warning -------------------------------------+------------------------------------- Reporter: ChaiTRex | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 7.10.4 Component: GHCi | 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: -------------------------------------+------------------------------------- Following the advice on [https://stackoverflow.com/a/27881726/7208029 an answer to "How can I load optimized code in GHCI?"], I get a GHCi panic. Running `ghc Luhn` succeeds just fine. On running `ghci Luhn`, I get: {{{ $ ghci Luhn GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Luhn ( Luhn.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): floatExpr tick break<15>() Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Contents of `Luhn.hs`: {{{#!hs {-# OPTIONS_GHC -fobject-code -O3 #-} module Luhn (checkLuhn) where import Data.Bits (shiftL) import Data.Char (digitToInt) import Data.List (foldl') -- Quickly gets a list of digits from a nonnegative Integer -- Gives error for negative inputs -- Uses GMP's show for greatly-improved speed over GMP's div and mod toDigits :: Integer -> [Int] {-# INLINE toDigits #-} toDigits = map digitToInt . show -- Quickly gets the same result as iteratively getting the digit sum of a nonnegative Int until the digit sum is only one digit long -- Gives an erroneous value for negative inputs repeatedDigitSum :: Int -> Int {-# INLINE repeatedDigitSum #-} repeatedDigitSum n = (n - 1) `rem` 9 + 1 -- Gets the Luhn sum, which is zero for valid inputs, of a list of digits -- Uses Data.Bits.shiftL to quickly double luhnSum :: [Int] -> Int {-# INLINE luhnSum #-} luhnSum = fromInteger . flip rem 10 . foldl' (+) 0 . zipWith ($) (cycle [toInteger, toInteger . repeatedDigitSum . flip shiftL 1]) -- Checks whether a nonnegative Integer passes the Luhn algorithm -- Negative inputs are False, since the Luhn algorithm is intended for unsigned inputs checkLuhn :: Integer -> Bool {-# INLINABLE checkLuhn #-} checkLuhn n = (n >= 0) && ((== 0) . luhnSum . reverse . toDigits) n }}} Strangely, `ghci -fobject-code -O3 Luhn` works just great, so apparently it's not a problem with the switches? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15317 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler