[GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit

GHC ghc-devs at haskell.org
Thu Mar 22 08:02:02 UTC 2018


#14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit
-------------------------------------+-------------------------------------
           Reporter:                 |             Owner:  (none)
  martijnbastiaan                    |
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:                 |  Operating System:  Linux
       Architecture:  x86_64         |   Type of failure:  Compile-time
  (amd64)                            |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code snippet:

 {{{#!hs
 module Test where

 import Data.Bits (setBit)
 import Data.List

 f :: Integer
 f = foldl setBit 0 toSet
   where
     toSet = [n | (n, _) <- zip [0..] [1]]
 }}}

 Fails to compile, yielding:

 {{{
 martijn at qbltop:~/code/scratch$ ghc Test.hs -O1
 [1 of 1] Compiling Test             ( Test.hs, Test.o )
 ghc: Out of memory
 }}}

 A few observations:

 - Compiling with no optimizations (-O0) works fine
 - I have not found a function other than setBit which triggers this
 behavior
 - Changing foldl to its strict brother foldl' does not help
 - Changing the type signature of "f" from "Integer" to "Int" causes the
 code to compile just fine

 I have been unable to reduce this example any further. I am using GHC
 8.2.1.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14962>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list