<div dir="ltr"><div><div><div>Hey,<br><br></div>the problem is with eta-expansion in this case, I believe, or rather the lack there-of.<br>Your recursive `f` is always bottoming out, which makes GHC not want to eta-expand the RealWorld# parameter (Note [State hack and bottoming functions] in CoreArity.hs is probably related).<br>If you change `f`s last branch to `return 2`, it's no longer (detectably) bottoming out and you get the 'desired' behavior:<br><br>test.exe: Prelude.undefined<br>CallStack (from HasCallStack):<br> error, called at libraries\base\GHC\Err.hs:79:14 in base:GHC.Err<br> undefined, called at test.hs:25:7 in main:Main<br><br></div>Greetings,<br></div>Sebastian<br><div><div><br><br><br></div></div></div><div class="gmail_extra"><br><div class="gmail_quote">2018-03-25 9:14 GMT+02:00 Ömer Sinan Ağacan <span dir="ltr"><<a href="mailto:omeragacan@gmail.com" target="_blank">omeragacan@gmail.com</a>></span>:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hi,<br>
<br>
In this program<br>
<br>
{-# LANGUAGE MagicHash #-}<br>
<br>
module Lib where<br>
<br>
import Control.Exception<br>
import GHC.Exts<br>
import <a href="http://GHC.IO" rel="noreferrer" target="_blank">GHC.IO</a><br>
<br>
data Err = Err<br>
deriving (Show)<br>
instance Exception Err<br>
<br>
f :: Int -> Int -> IO Int<br>
f x y | x > 0 = IO (raiseIO# (toException Err))<br>
| y > 0 = return 1<br>
| otherwise = return 2<br>
<br>
when I compile this with 8.4 -O2 I get a strict demand on `y`:<br>
<br>
f :: Int -> Int -> IO Int<br>
[GblId,<br>
Arity=3,<br>
Str=<S(S),1*U(U)><S(S),1*U(U)><wbr><S,U>,<br>
...]<br>
<br>
but clearly `y` is not used on all code paths, so I don't understand why we<br>
have a strict demand here.<br>
<br>
I found this example in the comments around `raiseIO#`:<br>
<br>
-- raiseIO# needs to be a primop, because exceptions in the IO monad<br>
-- must be *precise* - we don't want the strictness analyser turning<br>
-- one kind of bottom into another, as it is allowed to do in pure code.<br>
--<br>
-- But we *do* want to know that it returns bottom after<br>
-- being applied to two arguments, so that this function is strict in y<br>
-- f x y | x>0 = raiseIO blah<br>
-- | y>0 = return 1<br>
-- | otherwise = return 2<br>
<br>
However it doesn't explain why we want be strict on `y`.<br>
<br>
Interestingly, when I try to make GHC generate a worker and a wrapper for this<br>
function to make the program fail by evaluating `y` eagerly I somehow got a<br>
lazy demand on `y`:<br>
<br>
{-# LANGUAGE MagicHash #-}<br>
<br>
module Main where<br>
<br>
import Control.Exception<br>
import GHC.Exts<br>
import <a href="http://GHC.IO" rel="noreferrer" target="_blank">GHC.IO</a><br>
<br>
data Err = Err<br>
deriving (Show)<br>
instance Exception Err<br>
<br>
f :: Int -> Int -> IO Int<br>
f x y | x > 0 = IO (raiseIO# (toException Err))<br>
| y > 0 = f x (y - 1)<br>
| otherwise = f (x - 1) y<br>
<br>
main = f 1 undefined<br>
<br>
I was thinking that this program should fail with "undefined" instead of "Err",<br>
but the demand I got for `f` became:<br>
<br>
f :: Int -> Int -> IO Int<br>
[GblId,<br>
Arity=2,<br>
Str=<S(S),1*U(U)><L,1*U(U)>,<br>
...]<br>
<br>
which makes sense to me. But I don't understand how my changes can change `y`s<br>
demand, and why the original demand is strict rather than lazy. Could anyone<br>
give me some pointers?<br>
<br>
Thanks<br>
<br>
Ömer<br>
______________________________<wbr>_________________<br>
ghc-devs mailing list<br>
<a href="mailto:ghc-devs@haskell.org">ghc-devs@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/ghc-devs</a><br>
</blockquote></div><br></div>