pseq strictness properties

Duncan Coutts duncan.coutts at worc.ox.ac.uk
Fri Nov 21 04:58:52 EST 2008


On Thu, 2008-11-20 at 15:33 -0800, Don Stewart wrote:
> duncan.coutts:
> > I don't think I'm just speaking for myself when I say that pseq is
> > confusing and the docs similarly.
> > 
> > Given the type
> > 
> > a -> b -> b
> > 
> > we would assume that it is lazy in it's first arg and strict in the
> > second. (Even in the presence of seq we know that it really really must
> > be strict in it's second arg since it returns it or _|_ in which case
> > it's still strict).
> > 
> > Of course we know of the seq primitive with this type that is strict in
> > both. However we also now have pseq that has the _opposite_ "static"
> > strictness to the original expected strictness.
> 
> Could you state "static" strictness as a StrictCheck property?
> I'm not quite sure what this distinction means, actually.

No, because StrictCheck can only check actual strictness properties. I
mean actually passing in _|_ and getting _|_ out, at runtime.

For pseq there is its actual strictness (it's strict in both args) but
then the strictness that we tell the optimiser is different. We claim
that it is lazy in it's second argument. That means that the optimiser
is not able to do certain transformations that it might otherwise do.
Basically it cannot propagate the strictness information upwards to
earlier expressions or callers.

-- "pseq" is defined a bit weirdly (see below)
--
-- The reason for the strange "lazy" call is that it
-- fools the compiler into thinking that pseq  and par are non-strict in
-- their second argument (even if it inlines pseq at the call site).
-- If it thinks pseq is strict in "y", then it often evaluates
-- "y" before "x", which is totally wrong.

{-# INLINE pseq  #-}
pseq :: a -> b -> b
pseq  x y = x `seq` lazy y

{-# INLINE par  #-}
par :: a -> b -> b
par  x y = case (par# x) of { _ -> lazy y }

The lazy x function is a primitive that is the same as id, except that
it lies to the optimiser and claims that it is not strict.

Duncan



More information about the Glasgow-haskell-users mailing list