#7556: build/fold causes with ByteString unpack causes huge memory leak
------------------------------------+---------------------------------------
Reporter:  glguy                    |          Owner:                  
    Type:  bug                      |         Status:  new             
Priority:  normal                   |      Component:  libraries/base  
 Version:  7.6.1                    |       Keywords:                  
      Os:  Unknown/Multiple         |   Architecture:  Unknown/Multiple
 Failure:  Runtime performance bug  |      Blockedby:                  
Blocking:                           |        Related:                  
------------------------------------+---------------------------------------

Comment(by glguy):

 {{{
 module Main where

 import qualified Data.ByteString as B
 import Data.Word (Word8)

 -- works fast without optimizations
 -- with optimizations this has a space leak
 -- seems related to fold/build fusion in foldr/unpack

 main :: IO ()
 main = do
   let b = B.replicate 100000000 1
   print $ B.length b
   print $ example1 b -- fast
   print $ example2 b -- slow

 search :: [Word8] -> Bool
 search [] = False
 search (x:xs) = x == 1 || search xs

 example1, example2 :: B.ByteString -> Bool
 example1 = search . B.unpack
 example2 = foldr (\x xs -> x == 1 || xs) False . B.unpack
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7556#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to