[GHC] #15673: ghc: panic! (the 'impossible' happened)

#15673: ghc: panic! (the 'impossible' happened) --------------------------------------+--------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: MacOS X Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- The following few lines produce a GHC panic: {{{#!hs module Main where import Data.Bits (shift) badOne :: [Int] -> Integer badOne is = sum $ zipWith (\n _->shift 1 n) (enumFrom 0) is main = return () :: IO () }}} The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore. The error message is: {{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}} All else is off-the-shelf stack lts-12.10 via {{{#!bash stack new bad-one simple }}} Tested on Mac OS X and Debian. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mcmayer): * failure: None/Unknown => GHC doesn't work at all -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by mcmayer: Old description:
The following few lines produce a GHC panic:
{{{#!hs module Main where
import Data.Bits (shift)
badOne :: [Int] -> Integer badOne is = sum $ zipWith (\n _->shift 1 n) (enumFrom 0) is
main = return () :: IO () }}}
The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore.
The error message is:
{{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}}
All else is off-the-shelf stack lts-12.10 via
{{{#!bash stack new bad-one simple }}}
Tested on Mac OS X and Debian.
New description: The following few lines produce a GHC panic: {{{#!hs module Main where import Data.Bits (shift) badOne :: [Int] -> Integer badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is main = return () :: IO () }}} The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore. The error message is: {{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}} All else is off-the-shelf stack lts-12.10 via {{{#!bash stack new bad-one simple }}} Tested on Mac OS X and Debian. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by mcmayer: Old description:
The following few lines produce a GHC panic:
{{{#!hs module Main where
import Data.Bits (shift)
badOne :: [Int] -> Integer badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is
main = return () :: IO () }}}
The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore.
The error message is:
{{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}}
All else is off-the-shelf stack lts-12.10 via
{{{#!bash stack new bad-one simple }}}
Tested on Mac OS X and Debian.
New description: The following few lines produce a GHC panic: {{{#!hs module Main where import Data.Bits (shift) badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is main = return () :: IO () }}} The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore. The error message is: {{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}} All else is off-the-shelf stack lts-12.10 via {{{#!bash stack new bad-one simple }}} Tested on Mac OS X and Debian. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: 14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mcmayer): * related: => 14959 Old description:
The following few lines produce a GHC panic:
{{{#!hs module Main where
import Data.Bits (shift)
badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is
main = return () :: IO () }}}
The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore.
The error message is:
{{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}}
All else is off-the-shelf stack lts-12.10 via
{{{#!bash stack new bad-one simple }}}
Tested on Mac OS X and Debian.
New description: The following few lines produce a GHC panic: {{{#!hs module Main where import Data.Bits (shift) badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is main = return () :: IO () }}} The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore. The error message is: {{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}} All else is off-the-shelf stack lts-12.10 via {{{#!bash stack new bad-one simple }}} Tested on Mac OS X and Debian. This has some resemblance to[https://ghc.haskell.org/trac/ghc/ticket/14959 #14959]. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: 14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by mcmayer: Old description:
The following few lines produce a GHC panic:
{{{#!hs module Main where
import Data.Bits (shift)
badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is
main = return () :: IO () }}}
The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore.
The error message is:
{{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}}
All else is off-the-shelf stack lts-12.10 via
{{{#!bash stack new bad-one simple }}}
Tested on Mac OS X and Debian.
This has some resemblance to[https://ghc.haskell.org/trac/ghc/ticket/14959 #14959].
New description: The following few lines produce a GHC panic: {{{#!hs module Main where import Data.Bits (shift) badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is main = return () :: IO () }}} The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore. The error message is: {{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}} All else is off-the-shelf stack lts-12.10 via {{{#!bash stack new bad-one simple }}} Tested on Mac OS X and Debian. This has some resemblance with [https://ghc.haskell.org/trac/ghc/ticket/14959 #14959]. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: 14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by mcmayer: Old description:
The following few lines produce a GHC panic:
{{{#!hs module Main where
import Data.Bits (shift)
badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is
main = return () :: IO () }}}
The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore.
The error message is:
{{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}}
All else is off-the-shelf stack lts-12.10 via
{{{#!bash stack new bad-one simple }}}
Tested on Mac OS X and Debian.
This has some resemblance with [https://ghc.haskell.org/trac/ghc/ticket/14959 #14959].
New description: The following few lines produce a GHC panic: {{{#!hs module Main where import Data.Bits (shift) badOne :: [Int] -> Integer -- replace Integer by Int and all is good! badOne is = sum $ zipWith (\n _->shift 1 n) [0..] is main = return () :: IO () }}} The function is stripped down as much as possible, it doesn't perform anything all to meaningful anymore. The error message is: {{{#!bash ghc: panic! (the 'impossible' happened) (GHC version 8.4.3 for x86_64-apple-darwin): heap overflow }}} All else is off-the-shelf stack lts-12.10 via {{{#!bash stack new bad-one simple }}} Tested on Mac OS X and Debian. This has some resemblance with [https://ghc.haskell.org/trac/ghc/ticket/14959 #14959], which was fixed in 8.4.2. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: heap overflow with Bits.shift and Integer -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.4 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: 14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: heap overflow with Bits.shift and Integer -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: 14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * os: MacOS X => Unknown/Multiple * milestone: 8.4.4 => 8.8.1 Comment: Confirmed on GHC HEAD and 8.4 on Linux. Note that you need to pass -O or -O2 to reproduce, with -O0 (the default) this compiles without any errors. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: heap overflow with Bits.shift and Integer -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: #14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * related: 14959 => #14959 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15673: heap overflow with Bits.shift and Integer
-------------------------------------+-------------------------------------
Reporter: mcmayer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: x86_64
Type of failure: GHC doesn't work | (amd64)
at all | Test Case:
Blocked By: | Blocking:
Related Tickets: #14959 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#15673: heap overflow with Bits.shift and Integer -------------------------------------+------------------------------------- Reporter: mcmayer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: GHC doesn't work | Test Case: at all | simplCore/should_compile/T15673 Blocked By: | Blocking: Related Tickets: #14959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => simplCore/should_compile/T15673 * status: new => closed * resolution: => fixed Comment: Thanks for reporting with nice repro case -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15673#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC