[GHC] #13535: vector test suite uses excessive memory on GHC 8.2
GHC
ghc-devs at haskell.org
Sat Jul 14 07:23:54 UTC 2018
#13535: vector test suite uses excessive memory on GHC 8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: new
Priority: high | Milestone: 8.8.1
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: #10800 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by harendra):
It looks like I am seeing this same bug on GHC 8.2.2. This is again in a
streaming library with stream fusion like vector and I am seeing the
problem specifically with the "filter" code in the library, though it does
not always happen, only in some cases. I have two branches in my repo that
reproduce the problem:
* See branch https://github.com/composewell/streamly/tree/ghc-8.2.2-bug .
The last commit on this branch
https://github.com/composewell/streamly/commit/8f08248eba6702159f7bc3fe99e0c2244592dbb0
disables the culprit code.
* The second branch is
https://github.com/composewell/streamly/tree/ghc-8.2.2-bug2 . The last
commit on this branch disables the culprit code.
The "filter" API code that is being used in these cases is defined in
https://github.com/composewell/streamly/blob/ghc-8.2.2-bug2/src/Streamly/Streams/StreamD.hs
. The code goes like this:
{{{
{-# INLINE_NORMAL filterM #-}
filterM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a
filterM f (Stream step state) = Stream step' state
where
{-# INLINE_LATE step' #-}
step' gst st = do
r <- step (rstState gst) st
case r of
Yield x s -> do
b <- f x
if b
then return $ Yield x s
else step' gst s
Stop -> return $ Stop
{-# INLINE filter #-}
filter :: Monad m => (a -> Bool) -> Stream m a -> Stream m a
filter f = filterM (return . f)
}}}
This is very much like the vector code, except that there is no Skip
constructor. I was originally thinking that it may have something to do
with the join point optimization. I hope this will shed some light on the
issue. I am not seeing the issue with GHC-8.4.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13535#comment:48>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list