#2754: Strictness analyzer fails on an implementation of foldl
-----------------------------+----------------------------------------------
Reporter: nimnul | Owner:
Type: feature request | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 6.8.3
Severity: normal | Resolution: invalid
Keywords: | Difficulty: Unknown
Testcase: | Architecture: x86
Os: Windows |
-----------------------------+----------------------------------------------
Comment (by igloo):
Replying to [comment:6 nimnul]:
> Replying to [comment:4 dons]:
> > nimul, this might explain the behaviour you see:
> >
> > {{{
> > -- We write foldl as a non-recursive thing, so that it
> > -- can be inlined, (skipped)
> }}}
>
> foldC is recursive, but is optimized correctly. So recursion in foldA is
not an argument.
Right, the strictness analyser understand recursion, that's not the
problem.
Let me try and explain the differences. With `foldl`:
{{{
foldl :: (a -> b -> a) -> a -> [b] -> a
foldl f z0 xs0 = lgo z0 xs0
where
lgo z [] = z
lgo z (x:xs) = lgo (f z x) xs
}}}
if you have a use
{{{
main = print $ foldl (+) 0 l
}}}
then GHC inlines the definition of `foldl` where it is used. The `(+)` is
then inlined for `f` in this copy of `foldl`, the strictness analyser can
tell that it is strict, and you get the behaviour that you want.
If you use `foldA` instead:
{{{
foldA :: (a -> e -> a) -> a -> [e] -> a
foldA _ r [] = r
foldA op r (x:xs) = foldA op (op r x) xs
}}}
then the definition won't be inlined, because GHC deliberately doesn't
inline recursive definitions. Instead, you get a call to the generic
`foldA` code, which can't assume that `op` is strict in its first
argument, so you get the large thunk built.
If you use `foldC`:
{{{
foldC r [] = r
foldC r (x:xs) = foldC ((+) r x) xs
}}}
then the strictness analyser can again see that the function you are using
(`(+)`) is strict and so you get the behaviour that you want. (actually,
this is only because you end up with a version specialised for `Int`; if
you define foldC in a different module then I suspect you'll get a large
thunk built again).
> Is there any reason why my case is not a failing simple test case for
GHC optimizer, and thus cannot be accepted as an enhancement request? The
current behaviour (not inlining op) and the desired behaviour (to inline
op if it's known to be strict and then proceed with already implemented
optimizations) are clear.
You could certainly make changes to the optimiser that make this case
better, but there would be other cases that those changes would make
worse.
This (`foldl (+)`) is a well-known example, and I don't think that having
this ticket open would be useful. I'm sure that if Simon disagrees then he
well re-open it.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2754#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs