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

GHC ghc-devs at haskell.org
Mon Sep 24 16:49:55 UTC 2018


#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


More information about the ghc-tickets mailing list