[GHC] #16357: Add `oneShot` to the implementation of foldlM
GHC
ghc-devs at haskell.org
Mon Feb 25 07:18:26 UTC 2019
#16357: Add `oneShot` to the implementation of foldlM
-------------------------------------+-------------------------------------
Reporter: autotaker | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 8.9
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by autotaker):
This bug is caused by INLINE annotation for `c` which is introduced while
fixing #8763.
After list fusion, the example program would be:
{{{#!hs
f (I# n) =
letrec go i =
case i `remInt#` 2 of
1# -> case i ==# n of
0# -> go (i +# 1)
1# -> pure
0# -> c (I# i) (case i ==# n of
0# -> go (i +# 1)
1# -> pure)
in go 0# (I# 0)
c x k z = k $! (z + x)
{-# INLINE c #-}
}}}
We can see function `c` is lifted to the **top-level definition**.
Besides, the continuation `case i ==# n of { 0# -> go (i +# 1); 1# -> pure
}`
is passed as a **higher-order** argument of `c`.
Therefore, CallArity analyzer cannot find the correct call-arity of
function `go`.
Without INLINE pragma for `c`, we have:
{{{#!hs
f (I# n) =
letrec go i =
case i `remInt#` 2 of
1# -> case i ==# n of
0# -> go (i +# 1)
1# -> pure
0# ->
let k = case i ==# n of
0# -> go (i +# 1)
1# -> pure in
\z -> k $! I# (z + (I# i))
in go 0# (I# 0)
}}}
We can see the continuation `k` is defined inside `go`.
In this case, CallArity works good and finds the call-arity of `go` as 3
(not 2 because it includes `State# Realworld`).
If we define `c x k = \z -> f z x >>= k` (instead of `c x k z = f z x >>=
k`) and add an INLINE pragma for `c`,
CallArity works good because the continuation is defined inside `go`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16357#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list