To seq or not to seq, that is the question

Are these equivalent? If not, under what circumstances are they not equivalent? When should you use each? evaluate a >> return b a `seq` return b return (a `seq` b) Furthermore, consider: - Does the answer change when a = b? In such a case, is 'return $! b' permissible? - What about when b = () (e.g. unit)? - What about when 'return b' is some arbitrary monadic value? - Does the underlying monad (e.g. if it is IO) make a difference? - What if you use pseq instead of seq? In http://hackage.haskell.org/trac/ghc/ticket/5129 we a bug in 'evaluate' deriving precisely from this confusion. Unfortunately, the insights from this conversation were never distilled into a widely publicized set of guidelines... largely because we never really figured out was going on! The purpose of this thread is to figure out what is really going on here, and develop a concrete set of guidelines which we can disseminate widely. Here is one strawman answer (which is too complicated to use in practice): - Use 'evaluate' when you mean to say, "Evaluate this thunk to HNF before doing any other IO actions, please." Use it as much as possible in IO. - Use 'return (a `seq` b)' for strictness concerns that have no relation to the monad. It avoids unnecessary strictness when the value ends up never being used and is good hygiene if the space leak only occurs when 'b' is evaluated but not 'a'. - Use 'return $! a' when you mean to say, "Eventually evaluate this thunk to HNF, but if you have other thunks which you need to evaluate to HNF, it's OK to do those first." In particular, (return $! a) >> (return $! b) === a `seq` (return $! b) === a `seq` b `seq` return b === b `seq` a `seq` return b [1] This situation is similar for 'a `seq` return ()' and 'a `seq` m'. Avoid using this form in IO; empirically, you're far more likely to run into stupid interactions with the optimizer, and when later monadic values maybe bottoms, the optimizer will be justified in its choice. Prefer using this form when you don't care about ordering, or if you don't mind thunks not getting evaluated when bottoms show up. For non-IO monads, since everything is imprecise anyway, it doesn't matter. - Use 'pseq' only when 'par' is involved. Edward

On Fri, Mar 08, 2013 at 08:53:15PM -0800, Edward Z. Yang wrote:
Are these equivalent? If not, under what circumstances are they not equivalent? When should you use each?
evaluate a >> return b [...] - Use 'evaluate' when you mean to say, "Evaluate this thunk to HNF before doing any other IO actions, please." Use it as much as possible in IO.
I've never looked at evaluate before but I've just found it's haddock and given it some thought. http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Exc... Since it is asserted that evaluate x = (return $! x) >>= return is it right to say (on an informal level at least) that evaluating an IO action to WHNF means evaluating it to the outermost >>= or return?
For non-IO monads, since everything is imprecise anyway, it doesn't matter.
Could you explain what you mean by "imprecise"? Tom

Excerpts from Tom Ellis's message of Sat Mar 09 00:34:41 -0800 2013:
I've never looked at evaluate before but I've just found it's haddock and given it some thought.
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Exc...
Since it is asserted that
evaluate x = (return $! x) >>= return
is it right to say (on an informal level at least) that evaluating an IO action to WHNF means evaluating it to the outermost >>= or return?
Sure. Prelude> let x = undefined :: IO a Prelude> x `seq` () *** Exception: Prelude.undefined Prelude> (x >>= undefined) `seq` () ()
For non-IO monads, since everything is imprecise anyway, it doesn't matter.
Could you explain what you mean by "imprecise"?
Imprecise as in imprecise exceptions, http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.h... Edward

On 13-03-08 11:53 PM, Edward Z. Yang wrote:
Are these equivalent? If not, under what circumstances are they not equivalent? When should you use each?
evaluate a >> return b a `seq` return b return (a `seq` b)
Let a = div 0 0 (or whatever pure but problematic expression you like) b can be the same as a or something else. First assume IO. The 3rd one is distinguished by main = m >> return () where m is to be plugged in the 1st, 2nd, or 3rd. During IO execution, the 1st and 2nd throw an exception, the 3rd one does not. The 2nd is distinguished by main = evaluate m During IO execution, the 2nd throws an exception, the 1st and 3rd do not. (m `seq` return () should also do the same.) In practice, we seldom artificially evaluate or seq an IO action like that. And so, that distinction between the 1st and 2nd is seldom observed. But another difference matters more in practice: main = head [] `seq` (a `seq` return b) Two consecutive seqs is an instance where the impreciseness of imprecise exceptions kicks in. The compiler reserves the right to prefer either the empty-list exception or the divide-by-0 exception; perhaps even a difference choice at a different time. Whereas: main = evaluate (head []) >> (evaluate a >> return b) By virtue of IO's serializing >> (and lack of unsafeInterleaveIO hehe), the exception thrown must be the empty-list one. If the monad is not IO, then we cannot discuss evaluate. But we can be sure that different monads behave differently, and the difference involves >>=. Example: import Control.Monad.State.Strict a = div 0 0 b = whatever you like main = print (evalState ((a `seq` return b) >> return ()) ()) -- throws an exception import Control.Monad.State.Lazy a = div 0 0 b = whatever you like main = print (evalState ((a `seq` return b) >> return ()) ()) -- does not throw an exception (Did you know: Control.Monad.State refers to the Lazy one.) I leave the rest of the questions unanswered. Enough mind-bending for today! :)

On Fri, Mar 08, 2013 at 08:53:15PM -0800, Edward Z. Yang wrote:
Are these equivalent? If not, under what circumstances are they not equivalent? When should you use each?
evaluate a >> return b a `seq` return b return (a `seq` b)
Furthermore, consider: [...] - Does the underlying monad (e.g. if it is IO) make a difference? [...]
Here's a monad transformer DelayT which adds an "evaluate" operation to any monad. Perhaps it will help in understanding the situation. (NB it only has the desired behaviour for monads which must force x to at least WHNF before they can perform the action associated with x >>= f, so Identity won't do, for example). % cat evaluate.hs && ghc -fforce-recomp evaluate.hs && ./evaluate import Control.Monad.Trans.Class (lift, MonadTrans) data DelayT m a = DelayT (m a) deriving Show unlift :: DelayT m a -> m a unlift (DelayT x) = x instance Monad m => Monad (DelayT m) where return = lift . return x >>= f = lift $ unlift x >>= unlift . f instance MonadTrans DelayT where lift = DelayT evaluate :: Monad m => a -> DelayT m a evaluate = lift . (return $!) type M = Maybe should_succeed :: Bool should_succeed = x `seq` () == () where x :: DelayT M () x = evaluate undefined should_fail :: DelayT M () should_fail = evaluate undefined >> return () main = do putStrLn "Should succeed" print should_succeed putStrLn "Should fail" print should_fail [1 of 1] Compiling Main ( evaluate.hs, evaluate.o ) Linking evaluate ... Should succeed True Should fail evaluate: Prelude.undefined
participants (3)
-
Albert Y. C. Lai
-
Edward Z. Yang
-
Tom Ellis