[GHC] #8962: compile hang and memory blowup when using profiling and optimization

GHC ghc-devs at haskell.org
Sun Apr 6 16:35:03 UTC 2014


#8962: compile hang and memory blowup when using profiling and optimization
-------------------------+-------------------------------------------------
       Reporter:  ghorn  |             Owner:
           Type:  bug    |            Status:  new
       Priority:         |         Milestone:
  normal                 |           Version:  7.8.1-rc2
      Component:         |  Operating System:  Linux
  Compiler               |   Type of failure:  Compile-time performance bug
       Keywords:         |         Test Case:
   Architecture:         |          Blocking:
  x86_64 (amd64)         |
     Difficulty:         |
  Unknown                |
     Blocked By:         |
Related Tickets:         |
-------------------------+-------------------------------------------------
 When I try to compile the following files:
 {{{
 -- Vectorize.hs
 {-# OPTIONS_GHC -Wall #-}
 {-# LANGUAGE TypeOperators #-}

 module Vectorize
        ( GVectorize(..)
        ) where

 import GHC.Generics
 import Data.Vector ( Vector )
 import qualified Data.Vector as V

 gvlength :: GVectorize f => f a -> Int
 gvlength = V.length . gvectorize . (gempty `asFunctorOf`)
   where
     asFunctorOf :: f a -> f b -> f a
     asFunctorOf x _ = x

 class GVectorize f where
   gdevectorize :: Vector a -> f a
   gvectorize :: f a -> Vector a
   gempty :: f ()

 instance (GVectorize f, GVectorize g) => GVectorize (f :*: g) where
   gdevectorize v0s
     | V.length v0s < n0 =
       error $ show n0
     | otherwise = f0 :*: f1
     where
       f0 = gdevectorize v0
       f1 = gdevectorize v1

       n0 = gvlength f0

       (v0,v1) = V.splitAt n0 v0s

   gvectorize (f :*: g) = gvectorize f V.++ gvectorize g
   gempty = gempty :*: gempty

 instance GVectorize f => GVectorize (M1 i c f) where
   gdevectorize = M1 . gdevectorize
   gvectorize = gvectorize . unM1
   gempty = undefined -- M1 gempty

 instance GVectorize Par1 where
   gdevectorize _ = undefined
   gvectorize = V.singleton . unPar1
   gempty = undefined -- Par1 ()
 }}}

 {{{
 -- Woo.hs
 {-# OPTIONS_GHC -Wall #-}
 {-# Language DeriveGeneric #-}

 module Woo
        ( Woo(..)
        , devectorize
        ) where

 import GHC.Generics
 import Data.Vector ( Vector )

 import Vectorize ( GVectorize(..) )

 data Woo a =
   MkWoo { x00 :: a
         , x01 :: a
         , x02 :: a
         , x03 :: a
         , x04 :: a
         , x05 :: a
         , x06 :: a
         , x07 :: a
         , x08 :: a
         , x09 :: a
         , x10 :: a
         , x11 :: a
         , x12 :: a
         , x13 :: a
         , x14 :: a
         , x15 :: a
         , x16 :: a
         , x17 :: a
         , x18 :: a
         , x19 :: a
         , x20 :: a
         , x21 :: a
         } deriving (Generic1)

 devectorize :: Vector a -> Woo a
 devectorize = to1 . gdevectorize
 }}}
 with `ghc -O2 -prof -fprof-auto-calls Woo.hs`, GHC seems to hang on Woo.o
 and the memory usage steadily creeps up (I killed it at 5GB after about 5
 minutes).

 I don't think this is #7068 / #7898 / #8960 because `-fno-spec-constr`
 doesn't fix it and the end of the -v3 output is:

 {{{
 ...
 ...
 *** SpecConstr:
 Result size of SpecConstr
   = {terms: 89,855, types: 125,614, coercions: 138,597}
 *** Simplifier:
 Result size of Simplifier iteration=1
   = {terms: 428,416, types: 555,965, coercions: 855,101}
 Result size of Simplifier
   = {terms: 428,386, types: 555,815, coercions: 626,125}
 *** Tidy Core:
 Result size of Tidy Core
   = {terms: 428,386, types: 555,815, coercions: 626,125}
 writeBinIface: 190 Names
 writeBinIface: 495 dict entries
 *** CorePrep:
 Result size of CorePrep
   = {terms: 533,584, types: 600,927, coercions: 626,125}
 *** Stg2Stg:
 *** CodeOutput:
 *** New CodeGen:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 }}}

 and then about another 100 lines of `*** CPSZ:` before it hangs.

 Removing either the optimization or profiling flags fixes the bug.

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


More information about the ghc-tickets mailing list