[GHC] #9073: small SPECIALIZE INLINE program taking gigabytes of memory to compile

GHC ghc-devs at haskell.org
Sun May 4 01:43:36 UTC 2014


#9073: small SPECIALIZE INLINE program taking gigabytes of memory to compile
-------------------------+-------------------------------------------------
       Reporter:  dagit  |             Owner:
           Type:  bug    |            Status:  new
       Priority:         |         Milestone:
  normal                 |           Version:  7.8.2
      Component:         |  Operating System:  Unknown/Multiple
  Compiler               |   Type of failure:  Compile-time performance bug
       Keywords:         |         Test Case:
   Architecture:         |          Blocking:
  Unknown/Multiple       |
     Difficulty:         |
  Unknown                |
     Blocked By:         |
Related Tickets:         |
-------------------------+-------------------------------------------------
 I have a small program that is taking 1+ GB of memory to compile.

 I've distilled the troublesome input down to the following:
 {{{
 {-# LANGUAGE BangPatterns #-}
 import Data.Vector

 knot :: Vector Double -> Int -> Double
 knot vs k = vs ! idx0
   where
   !idx0 = abs k `mod` 16
 {-# SPECIALIZE INLINE knot :: Vector Double -> Int -> Double #-}

 noise :: Vector Double -> Int -> Double
 noise vs k =
   knot vs k + knot vs k + knot vs k + knot vs k +
   knot vs k + knot vs k + knot vs k + knot vs k
 }}}

 Compiled with `ghc -fprof-auto -prof -O2 -Wall`. As far as I can tell,
 prof-auto, prof, and optimizations of at least -O1 are required to trigger
 it.

 I'm using ghc-7.8.2 64bit for Windows. vector is version 0.10.9.1
 (currently the latest on hackage). Same code worked fine on ghc 7.6.2.

 Also worth noting: Even though the `SPECIALIZE` isn't needed, if you
 remove the `SPECIALIZE` or the `INLINE` the problem goes away. If you
 remove even one of the duplicated calls to `knot vs k` in the body of
 `noise` then the amount of memory required drops dramatically. Add more to
 increase the requirements. I've been able to push it up around 10 GB, but
 I don't have enough memory to test beyond that!

 Thanks!

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


More information about the ghc-tickets mailing list