[GHC] #15317: GHCi panic when trying to avoid GHC_OPTIONS -O warning

#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

#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 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------+-------------------------------------- Changes (by ChaiTRex): * failure: None/Unknown => GHCi crash * os: Unknown/Multiple => Linux * architecture: Unknown/Multiple => x86_64 (amd64) Old description:
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?
New description: 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? ---- `ghc --version`: {{{ The Glorious Glasgow Haskell Compilation System, version 7.10.3 }}} Ubuntu (and presumably Debian) package information: {{{ ghc: Installed: 7.10.3-7 Candidate: 7.10.3-7 Version table: *** 7.10.3-7 500 500 http://mirror.atlantic.net/ubuntu xenial/universe amd64 Packages 100 /var/lib/dpkg/status }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15317#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15317: GHCi panic when trying to avoid GHC_OPTIONS -O warning -------------------------------------+------------------------------------- Reporter: ChaiTRex | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #10965 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * os: Linux => Unknown/Multiple * related: => #10965 * architecture: x86_64 (amd64) => Unknown/Multiple * milestone: 7.10.4 => * resolution: => duplicate Comment: Thanks for the bug report. This is a duplicate of #10965, which has been fixed, so I recommend upgrading to use GHC 8.2 or later, which does not exhibit this issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15317#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC