Curious demand in a function parameter

Simon Peyton Jones simonpj at microsoft.com
Mon Mar 26 09:34:06 UTC 2018


|  but clearly `y` is not used on all code paths, so I don't understand
|  why we have a strict demand here.

Why is f strict in y?

Consider

factorial n acc
  | n <0 = error "bad arg"
  | n==1 = acc
  | otherwise = factorial (n-1) (n*acc)

Is this strict in 'acc'.  GHC says "yes" because it's MUCH more efficient to be strict in 'acc'; and we don’t to the thrown off by the error case.

Also, formally, is  (factorial n bottom) equal to bottom? Yes, even if n<0, because error returns bottom.


---------------

|  Interestingly, when I try to make GHC generate a worker and a wrapper
|  for this function to make the program fail by evaluating `y` eagerly I
|  somehow got a lazy demand on `y`:

That's a little more surprising to me, but as Sebastian point out you have now written a function that ALWAYS returns bottom.  That's not a very interesting function!  And GHC doesn't make much effort to optimise it.  I have not looked into why GHC doesn't eta-expand guaranteed-bottom functions, but I bet there's a note about it.  And I don't care much!

Simon


|  -----Original Message-----
|  From: ghc-devs <ghc-devs-bounces at haskell.org> On Behalf Of Ömer Sinan
|  Agacan
|  Sent: 25 March 2018 08:14
|  To: ghc-devs <ghc-devs at haskell.org>
|  Subject: Curious demand in a function parameter
|  
|  Hi,
|  
|  In this program
|  
|      {-# LANGUAGE MagicHash #-}
|  
|      module Lib where
|  
|      import Control.Exception
|      import GHC.Exts
|      import GHC.IO
|  
|      data Err = Err
|        deriving (Show)
|      instance Exception Err
|  
|      f :: Int -> Int -> IO Int
|      f x y | x > 0     = IO (raiseIO# (toException Err))
|            | y > 0     = return 1
|            | otherwise = return 2
|  
|  when I compile this with 8.4 -O2 I get a strict demand on `y`:
|  
|      f :: Int -> Int -> IO Int
|      [GblId,
|       Arity=3,
|       Str=<S(S),1*U(U)><S(S),1*U(U)><S,U>,
|       ...]
|  
|  but clearly `y` is not used on all code paths, so I don't understand
|  why we have a strict demand here.
|  
|  I found this example in the comments around `raiseIO#`:
|  
|      -- raiseIO# needs to be a primop, because exceptions in the IO
|  monad
|      -- must be *precise* - we don't want the strictness analyser
|  turning
|      -- one kind of bottom into another, as it is allowed to do in pure
|  code.
|      --
|      -- But we *do* want to know that it returns bottom after
|      -- being applied to two arguments, so that this function is strict
|  in y
|      --     f x y | x>0       = raiseIO blah
|      --           | y>0       = return 1
|      --           | otherwise = return 2
|  
|  However it doesn't explain why we want be strict on `y`.
|  
|  Interestingly, when I try to make GHC generate a worker and a wrapper
|  for this function to make the program fail by evaluating `y` eagerly I
|  somehow got a lazy demand on `y`:
|  
|      {-# LANGUAGE MagicHash #-}
|  
|      module Main where
|  
|      import Control.Exception
|      import GHC.Exts
|      import GHC.IO
|  
|      data Err = Err
|        deriving (Show)
|      instance Exception Err
|  
|      f :: Int -> Int -> IO Int
|      f x y | x > 0     = IO (raiseIO# (toException Err))
|            | y > 0     = f x (y - 1)
|            | otherwise = f (x - 1) y
|  
|      main = f 1 undefined
|  
|  I was thinking that this program should fail with "undefined" instead
|  of "Err", but the demand I got for `f` became:
|  
|      f :: Int -> Int -> IO Int
|      [GblId,
|       Arity=2,
|       Str=<S(S),1*U(U)><L,1*U(U)>,
|       ...]
|  
|  which makes sense to me. But I don't understand how my changes can
|  change `y`s demand, and why the original demand is strict rather than
|  lazy. Could anyone give me some pointers?
|  
|  Thanks
|  
|  Ömer
|  _______________________________________________
|  ghc-devs mailing list
|  ghc-devs at haskell.org
|  https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.h
|  askell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devs&data=02%7C01%7Csimonpj%40microsoft.com%7C79b17f4f38684f15c4a308d5
|  9220339a%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6365755894481854
|  06&sdata=T7ZJjz%2Bek5CFAUYtt9CmEkRLIml0OAj8yEU5fTsuFC0%3D&reserved=0


More information about the ghc-devs mailing list