
#9390: Inlining prevents evaluation of ignored parts of unboxed tuples
-------------------------------------+-------------------------------------
Reporter: snoyberg | Owner:
Type: bug | Status: merge
Priority: normal | Milestone: 7.8.4
Component: Compiler | Version: 7.8.3
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: Incorrect | Difficulty: Unknown
result at runtime | Blocked By:
Test Case: | Related Tickets:
simplCore/should_run/T9390 |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
Oh yes thanks!
'''First point'''. I really don't like the reasoning though. How would
you explain to a client of `unsafePerformIO` what the specification is?
Perhaps "the effects of the `unsafePerformIO` are all performed before the
result is evaluated". But that is not true if the effects somehow depend
strictly on the value concerned. If it's hard to specify, we should be
cautious about relying on it.
After all, the example
{{{
unsafeDupablePerformIO (\s -> let r = f x in
case writeIORef v r s of (# s1, _ #) ->
(# s1, r #) )
}}}
really '''is''' strict in `r`. If you evaluate it, since `writeIORef`
returns `r`, it's clear that `r` will be evaluated. Saying "I want to
write the reference before evaluating `r` is very delicate!". Moreover
you can achieve the same effect, where it matters, with less magic. Here
is the current code from `libraries/base/tests/Memo2.lhs`:
{{{
memo' f ref weak_ref = \k -> unsafePerformIO $
do { ...blah...
; case lkp of
Just res -> do { putMVar ref (size,table); return res }
Nothing -> do { let res = f k
; ...blah...
; return res }
}}}
Now if we make the argument function given to `unsafePerformIO` return a
1-tuple thus, we are good:
{{{
memo' f ref weak_ref = \k -> case do_effects k of {# result #) -> result
where
do_effects k = unsafePerformIO $
do { ...blah...
; case lkp of
Just res -> do { putMVar ref (size,table); return (# res
#) }
Nothing -> do { let res = f k
; ...blah...
; return {# res #) }
}}}
Mind you (thinking aloud here), I suppose that this does rely on the
strictness analyser not being super-clever. If `unsafePerformIO`'s
signature was clever enough to say "in demand d, I call my function
argument and evaluate the second component the result with demand d" then
we'd be back in the same boat as before.
Another, perhaps more robust alternative, would be to say:
{{{
memo' f ref weak_ref = \k -> unsafePerformIO $
do { ...blah...
; case lkp of
Just res -> do { putMVar ref (size,table); return res }
Nothing -> do { let res = f k
; ...blah...
; return (lazy res) }
}}}
Here the `lazy` means that the `res` binding is not strict.
Anyway the point it that this subtle stuff should be visible in the
caller, for the rare moments when it is needed, rather than hidden in
`unsafePerformIO`.
All that said, there is is, and I suppose it may break things in rather
subtle ways if we remove it. So perhaps we should leave specifically
leave it un-documented!
'''Second point'''. I think it would be clearer as
{{{
unsafeDupablePerformIO (IO m) = case m realWorld# of (# _, r #) -> lazy r
}}}
That is, make the laziness wrap the 'r' part only, which is the important
bit here. I tried this:
{{{
{-# NOINLINE u1 #-}
u1 :: IO a -> a
u1 (IO m) = lazy (case m realWorld# of (# _, r #) -> r)
{-# NOINLINE u2 #-}
u2 :: IO a -> a
u2 (IO m) = case m realWorld# of (# _, r #) -> lazy r
{-# NOINLINE u3 #-}
u3 :: IO a -> a
u3 (IO m) = case m realWorld# of (# _, r #) -> r
}}}
and got this in the interface file:
{{{
u1 :: GHC.Types.IO a -> a
{- Arity: 1, HasNoCafRefs, Strictness: