Re: [GHC] #7556: build/fold causes with ByteString unpack causes huge memory leak
#7556: build/fold causes with ByteString unpack causes huge memory leak --+- Reporter: glguy | Owner: duncan Type: bug| Status: new Priority: normal | Milestone: 7.8.1 Component: libraries (other) | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: Runtime performance bug Difficulty: Unknown|Testcase: Blockedby: |Blocking: Related: | --+- Comment(by duncan): Crikey that's some old code. It's also totally wrong, as are the implementations of `foldl` and `foldr`. Patch in the works. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7556#comment:4 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
Re: [GHC] #7556: build/fold causes with ByteString unpack causes huge memory leak
#7556: build/fold causes with ByteString unpack causes huge memory leak --+- Reporter: glguy| Owner: duncan Type: bug | Status: closed Priority: normal | Milestone: 7.8.1 Component: libraries (other)|Version: 7.6.1 Resolution: fixed| Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: Runtime performance bug | Difficulty: Unknown Testcase: | Blockedby: Blocking: |Related: --+- Changes (by duncan): * status: new = closed * resolution: = fixed Comment: Fixed in bytestring head, will be in next point releases. {{{ Tue Jan 8 16:43:21 GMT 2013 Duncan Coutts dun...@community.haskell.org * Re-implement the foldr and foldl functions and fix unpack fusion They were just wrong. The old foldr and foldl were doing strict accumulation when they should be lazy. Also, the fusion for (List.foldr f z . BS.unpack) was using a tail-recursive variant on foldr (though not strictly accumulating) which meant it would build up a huge chain of thunks when it should be lazy and run in linear space. See ghc ticket 7556 }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7556#comment:5 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
Re: [GHC] #7556: build/fold causes with ByteString unpack causes huge memory leak
#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 1 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
Re: [GHC] #7556: build/fold causes with ByteString unpack causes huge memory leak
#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: +--- Changes (by shachaf): * cc: shachaf@… (added) Comment: The issue is [http://hackage.haskell.org/packages/archive/bytestring/0.10.2.0/doc/html/src /Data-ByteString.html#unpackFoldr here]: {{{ unpack ps = build (unpackFoldr ps) {-# INLINE unpack #-} -- -- Have unpack fuse with good list consumers -- -- critical this isn't strict in the acc -- as it will break in the presence of list fusion. this is a known -- issue with seq and build/foldr rewrite rules, which rely on lazy -- demanding to avoid bottoms in the list. -- unpackFoldr :: ByteString - (Word8 - a - a) - a - a unpackFoldr (PS fp off len) f ch = withPtr fp $ \p - do let loop q n_ | q `seq` n `seq` False = undefined -- n.b. loop _ (-1) acc = return acc loop q nacc = do a - peekByteOff q n loop q (n-1) (a `f` acc) loop (p `plusPtr` off) (len-1) ch {-# INLINE [0] unpackFoldr #-} {-# RULES ByteString unpack-list [1] forall p . unpackFoldr p (:) [] = unpackBytes p }}} When we use `foldr`, `foldr/build` fusion turns the whole expression into an application of `unpackFoldr`, which is tail recursive and therefore not sufficiently lazy -- but also not strict in the accumulator, so it builds up a big thunk. In `example1`, fusion doesn't happen, so the fold happens over `unpackBytes` instead, which generates list in small chunks that can be processed lazily. This looks like a `bytestring` bug to me. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7556#comment:2 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
Re: [GHC] #7556: build/fold causes with ByteString unpack causes huge memory leak
#7556: build/fold causes with ByteString unpack causes huge memory leak --+- Reporter: glguy | Owner: duncan Type: bug| Status: new Priority: normal | Milestone: 7.8.1 Component: libraries (other) | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: Runtime performance bug Difficulty: Unknown|Testcase: Blockedby: |Blocking: Related: | --+- Changes (by igloo): * owner: = duncan * difficulty: = Unknown * component: libraries/base = libraries (other) * milestone: = 7.8.1 Comment: Thanks for the diagnosis. Duncan, could you take a look please? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7556#comment:3 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