Skip to content

Subsequent strictness defeats pseq

Summary

Today, pseq x y expands to case x of !_ -> lazy y. We reason that the use of lazy will prevent us from moving the evaluation of y before the evaluation of x. Even if that much is true (CSE could potentially defeat it), if x is used strictly later on we may defer the eval on x.

Se also #22935

Steps to reproduce

compile and run with -O
{-# LANGUAGE BangPatterns #-}
module Main (main) where

import GHC.Conc
import GHC.Exts
import Debug.Trace

data StrictPair a b = SP !a !b
  deriving Show

f :: a -> Int -> StrictPair a Int
{-# NOINLINE f #-}
f x y = SP x (y * y)

fun :: a -> b -> (b -> Bool) -> StrictPair a Int
fun x y g = case pseq x y of
  !u -> case g u of
    True -> f x 12
    False -> f x 14

p :: Int
{-# NOINLINE p #-}
p = trace "eval p" 3

q :: Int
{-# NOINLINE q #-}
q = trace "eval q" 4

main :: IO ()
main = print (fun p q even)

In this program, q should never be evaluated unless p has already been evaluated, because it is only ever used as the second arg to pseq. But when it is run with optimizations, q will be evaluated first.

Environment

  • GHC version used: any version 8.0-9.6.1
Edited by Simon Peyton Jones
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information