Can pseq be defined in terms of seq? - haskell

As far as I know, seq a b evaluates (forces) a and b before returning b. It does not guarantee that a is evaluated first.
pseq a b evaluates a first, then evaluates/returns b.
Now consider the following:
xseq a b = (seq a id) b
Function application needs to evaluate the left operand first (to get a lambda form), and it can't blindly evaluate the right operand before entering the function because that would violate Haskell's non-strict semantics.
Therefore (seq a id) b must evaluate seq a id first, which forces a and id (in some unspecified order (but evaluating id does nothing)), then returns id b (which is b); therefore xseq a b evaluates a before b.
Is xseq a valid implementation of pseq? If not, what's wrong with the above argument (and is it possible to define pseq in terms of seq at all)?

The answer seems to be "no, at least not without additional magic".
The problem with
xseq a b = (seq a id) b
is that the compiler can see that the result of seq a id is id, which is strict everywhere. Function application is allowed to evaluate the argument first if the function is strict, because then doing so does not change the semantics of the expression. Therefore an optimizing compiler could start evaluating b first because it knows it will eventually need it.

Can pseq be defined in terms of seq?
In GHC - yes.
As noted by Alec, you'll also need the mirror-smoke lazy:
-- for GHC 8.6.5
import Prelude(seq)
import GHC.Base(lazy)
infixr 0 `pseq`
pseq :: a -> b -> b
pseq x y = x `seq` lazy y
the definition matching its counterpart in the GHC sources; the imports are
very different.
For other Haskell implementations, this may work:
import Prelude(seq)
infixr 0 `pseq`
pseq :: a -> b -> b
pseq x y = x `seq` (case x of _ -> y)
possibly in conjunction with - at the very least - the equivalent of:
-- for GHC 8.6.5
{-# NOINLINE pseq #-}
I'll let melpomene decide if that also qualifies as mirror-smoke...

Related

Strictness of dataToTag argument

In GHC.Prim, we find a magical function named dataToTag#:
dataToTag# :: a -> Int#
It turns a value of any type into an integer based on the data constructor it uses. This is used to speed up derived implementations of Eq, Ord, and Enum. In the GHC source, the docs for dataToTag# explain that the argument should already by evaluated:
The dataToTag# primop should always be applied to an evaluated argument.
The way to ensure this is to invoke it via the 'getTag' wrapper in GHC.Base:
getTag :: a -> Int#
getTag !x = dataToTag# x
It makes total sense to me that we need to force x's evaluation before dataToTag# is called. What I do not get is why the bang pattern is sufficient. The definition of getTag is just syntactic sugar for:
getTag :: a -> Int#
getTag x = x `seq` dataToTag# x
But let's turn to the docs for seq:
A note on evaluation order: the expression seq a b does not guarantee that a will be evaluated before b. The only guarantee given by seq is that the both a and b will be evaluated before seq returns a value. In particular, this means that b may be evaluated before a. If you need to guarantee a specific order of evaluation, you must use the function pseq from the "parallel" package.
In the Control.Parallel module from the parallel package, the docs elaborate further:
... seq is strict in both its arguments, so the compiler may, for example, rearrange a `seq` b into b `seq` a `seq` b ...
How is it that getTag is guaranteed to behave work, given that seq is insufficient for controlling evaluation order?
GHC tracks certain information about each primop. One key datum is whether the primop "can_fail". The original meaning of this flag is that a primop can fail if it can cause a hard fault. For example, array indexing can cause a segmentation fault if the index is out of range, so indexing operations can fail.
If a primop can fail, GHC will restrict certain transformations around it, and in particular won't float it out of any case expressions. It would be rather bad, for example, if
if n < bound
then unsafeIndex c n
else error "out of range"
were compiled to
case unsafeIndex v n of
!x -> if n < bound
then x
else error "out of range"
One of these bottoms is an exception; the other is a segfault.
dataToTag# is marked can_fail. So GHC sees (in Core) something like
getTag = \x -> case x of
y -> dataToTag# y
(Note that case is strict in Core.) Because dataToTag# is marked can_fail, it won't be floated out of any case expressions.

Would you ever write seq x x?

I'm not entirely clear on how seq works in Haskell.
It seems like it there are lots of cases where it would be useful to write
seq x x
and maybe even define a function:
strict x = seq x x
but such a function doesn't already exist so I'm guessing this approach is somehow wrongheaded. Could someone tell me if this is meaningful or useful?
seq a b returns the value of b, but makes that value depend on the evaluation of a. Thus, seq a a is exactly the same thing as a.
I think the misunderstanding here is that seq doesn't take any action, because pure functions don't take actions, it just introduces a dependency.
There is a function evaluate :: a -> IO () in Control.Exception that does what you want (note that it's in IO). They put it in exception because it's useful to see if the evaluation of an expression would throw, and if so handle the exception.
The expression x = seq a b means that if x is evaluated, then a will also be evaluated (but x will be equal to b).
It does not mean "evaluate a now".
Notice that if x is being evaluated, then since x equals b, then b will also be evaluated.
And hence, if I write x = seq a a, I am saying "if x is evaluated then evaluate a". But if I just do x = a, that would achieve exactly the same thing.
When you say seq a b what you are telling the computer is,
Whenever you need to evaluate b, evaluate a for me too, please.
If we replace both a and b with x you can see why it's useless to write seq x x:
Whenever you need to evaluate x, evaluate x for me too, please.
Asking the computer to evaluate x when it needs to evaluate x is just a useless thing to do – it was going to evaluate x anyway!
seq does not evaluate anything – it simply tells the computer that when you need the second argument, also evaluate the first argument. Understanding this is actually really important, because it allows you to understand the behaviour of your programs much better.
seq x x would be entirely, trivially redundant.
Remember, seq is not a command. The presence of a seq a b in your program does not force evaluation of a or b What it does do, is it makes the evaluation of the result artificially dependent on the evaluation of a, even though the result itself is b If you print out seq a b, a will be evaluated and its result discarded.. Since x already depends on itself, seq x x is silly.
Close! deepseq (which is the "more thorough" seq -- see the docs for a full description) has the type NFData a => a -> b -> b, and force (with type NFData a => a -> a) is defined simply as
force :: (NFData a) => a -> a
force x = x `deepseq` x

Memoizing multiplication

My application multiplies vectors after a (costly) conversion using an FFT. As a result, when I write
f :: (Num a) => a -> [a] -> [a]
f c xs = map (c*) xs
I only want to compute the FFT of c once, rather than for every element of xs. There really isn't any need to store the FFT of c for the entire program, just in the local scope.
I attempted to define my Num instance like:
data Foo = Scalar c
| Vec Bool v -- the bool indicates which domain v is in
instance Num Foo where
(*) (Scalar c) = \x -> case x of
Scalar d -> Scalar (c*d)
Vec b v-> Vec b $ map (c*) v
(*) v1 = let Vec True v = fft v1
in \x -> case x of
Scalar d -> Vec True $ map (c*) v
v2 -> Vec True $ zipWith (*) v (fft v2)
Then, in an application, I call a function similar to f (which works on arbitrary Nums) where c=Vec False v, and I expected that this would be just as fast as if I hack f to:
g :: Foo -> [Foo] -> [Foo]
g c xs = let c' = fft c
in map (c'*) xs
The function g makes the memoization of fft c occur, and is much faster than calling f (no matter how I define (*)). I don't understand what is going wrong with f. Is it my definition of (*) in the Num instance? Does it have something to do with f working over all Nums, and GHC therefore being unable to figure out how to partially compute (*)?
Note: I checked the core output for my Num instance, and (*) is indeed represented as nested lambdas with the FFT conversion in the top level lambda. So it looks like this is at least capable of being memoized. I have also tried both judicious and reckless use of bang patterns to attempt to force evaluation to no effect.
As a side note, even if I can figure out how to make (*) memoize its first argument, there is still another problem with how it is defined: A programmer wanting to use the Foo data type has to know about this memoization capability. If she wrote
map (*c) xs
no memoization would occur. (It must be written as (map (c*) xs)) Now that I think about it, I'm not entirely sure how GHC would rewrite the (*c) version since I have curried (*). But I did a quick test to verify that both (*c) and (c*) work as expected: (c*) makes c the first arg to *, while (*c) makes c the second arg to *. So the problem is that it is not obvious how one should write the multiplication to ensure memoization. Is this just an inherent downside to the infix notation (and the implicit assumption that the arguments to * are symmetric)?
The second, less pressing issue is that the case where we map (v*) onto a list of scalars. In this case, (hopefully) the fft of v would be computed and stored, even though it is unnecessary since the other multiplicand is a scalar. Is there any way around this?
Thanks
I believe stable-memo package could solve your problem. It memoizes values not using equality but by reference identity:
Whereas most memo combinators memoize based on equality, stable-memo does it based on whether the exact same argument has been passed to the function before (that is, is the same argument in memory).
And it automatically drops memoized values when their keys are garbage collected:
stable-memo doesn't retain the keys it has seen so far, which allows them to be garbage collected if they will no longer be used. Finalizers are put in place to remove the corresponding entries from the memo table if this happens.
So if you define something like
fft = memo fft'
where fft' = ... -- your old definition
you'll get pretty much what you need: Calling map (c *) xs will memoize the computation of fft inside the first call to (*) and it gets reused on subsequent calls to (c *). And if c is garbage collected, so is fft' c.
See also this answer to How to add fields that only cache something to ADT?
I can see two problems that might prevent memoization:
First, f has an overloaded type and works for all Num instances. So f cannot use memoization unless it is either specialized (which usually requires a SPECIALIZE pragma) or inlined (which may happen automatically, but is more reliable with an INLINE pragma).
Second, the definition of (*) for Foo performs pattern matching on the first argument, but f multiplies with an unknown c. So within f, even if specialized, no memoization can occur. Once again, it very much depends on f being inlined, and a concrete argument for c to be supplied, so that inlining can actually appear.
So I think it'd help to see how exactly you're calling f. Note that if f is defined using two arguments, it has to be given two arguments, otherwise it cannot be inlined. It would furthermore help to see the actual definition of Foo, as the one you are giving mentions c and v which aren't in scope.

the seq function and strictness

I have been wondering about this a lot, but I haven't been able to find anything about it.
When using the seq function, how does it then really work? Everywhere, it is just explained saying that seq a b evaluates a, discards the result and returns b.
But what does that really mean? Would the following result in strict evaluation:
foo s t = seq q (bar q t) where
q = s*t
What I mean is, is q strictly evaluated before being used in bar? And would the following be equivalent:
foo s t = seq (s*t) (bar (s*t) t)
I find it a little hard getting specifics on the functionality of this function.
You're not alone. seq is probably one of the most difficult Haskell functions to use properly, for a few different reasons. In your first example:
foo s t = seq q (bar q t) where
q = s*t
q is evaluated before bar q t is evaluated. If bar q t is never evaluated, q won't be either. So if you have
main = do
let val = foo 10 20
return ()
as val is never used, it won't be evaluated. So q won't be evaluated either. If you instead have
main = print (foo 10 20)
the result of foo 10 20 is evaluated (by print), so within foo q is evaluated before the result of bar.
This is also why this doesn't work:
myseq x = seq x x
Semantically, this means the first x will be evaluated before the second x is evaluated. But if the second x is never evaluated, the first one doesn't need to be either. So seq x x is exactly equivalent to x.
Your second example may or may not be the same thing. Here, the expression s*t will be evaluated before bar's output, but it may not be the same s*t as the first parameter to bar. If the compiler performs common sub-expression elimination, it may common-up the two identical expressions. GHC can be fairly conservative about where it does CSE though, so you can't rely on this. If I define bar q t = q*t it does perform the CSE and evaluate s*t before using that value in bar. It may not do so for more complex expressions.
You might also want to know what is meant by strict evaluation. seq evaluates the first argument to weak head normal form (WHNF), which for data types means unpacking the outermost constructor. Consider this:
baz xs y = seq xs (map (*y) xs)
xs must be a list, because of map. When seq evaluates it, it will essentially transform the code into
case xs of
[] -> map (*y) xs
(_:_) -> map (*y) xs
This means it will determine if the list is empty or not, then return the second argument. Note that none of the list values are evaluated. So you can do this:
Prelude> seq [undefined] 4
4
but not this
Prelude> seq undefined 5
*** Exception: Prelude.undefined
Whatever data type you use for seqs first argument, evaluating to WHNF will go far enough to figure out the constructor and no further. Unless the data type has components that are marked as strict with a bang pattern. Then all the strict fields will also be evaluated to WHNF.
Edit: (thanks to Daniel Wagner for suggestion in comments)
For functions, seq will evaluate the expression until the function "has a lambda showing", which means that it's ready for application. Here are some examples that might demonstrate what this means:
-- ok, lambda is outermost
Prelude> seq (\x -> undefined) 'a'
'a'
-- not ok. Because of the inner seq, `undefined` must be evaluated before
-- the lambda is showing
Prelude> seq (seq undefined (\x -> x)) 'b'
*** Exception: Prelude.undefined
If you think of a lambda binding as a (built-in) data constructor, seq on functions is perfectly consistent with using it on data.
Also, "lambda binding" subsumes all types of function definitions, whether defined by lambda notation or as a normal function.
The Controversy section of the HaskellWiki's seq page has a little about some of the consequences of seq in relation to functions.
You can think of seq as:
seq a b = case a of
_ -> b
This will evaluate a to head-normal form (WHNF) and then continue with evaluating b.
Edit after augustss comment: this case ... of is the strict, GHC Core one, which always forces its argument.

Evaluation strategy

How should one reason about function evaluation in examples like the following in Haskell:
let f x = ...
x = ...
in map (g (f x)) xs
In GHC, sometimes (f x) is evaluated only once, and sometimes once for each element in xs, depending on what exactly f and g are. This can be important when f x is an expensive computation. It has just tripped a Haskell beginner I was helping and I didn't know what to tell him other than that it is up to the compiler. Is there a better story?
Update
In the following example (f x) will be evaluated 4 times:
let f x = trace "!" $ zip x x
x = "abc"
in map (\i -> lookup i (f x)) "abcd"
With language extensions, we can create situations where f x must be evaluated repeatedly:
{-# LANGUAGE GADTs, Rank2Types #-}
module MultiEvG where
data BI where
B :: (Bounded b, Integral b) => b -> BI
foo :: [BI] -> [Integer]
foo xs = let f :: (Integral c, Bounded c) => c -> c
f x = maxBound - x
g :: (forall a. (Integral a, Bounded a) => a) -> BI -> Integer
g m (B y) = toInteger (m + y)
x :: (Integral i) => i
x = 3
in map (g (f x)) xs
The crux is to have f x polymorphic even as the argument of g, and we must create a situation where the type(s) at which it is needed can't be predicted (my first stab used an Either a b instead of BI, but when optimising, that of course led to only two evaluations of f x at most).
A polymorphic expression must be evaluated at least once for each type it is used at. That's one reason for the monomorphism restriction. However, when the range of types it can be needed at is restricted, it is possible to memoise the values at each type, and in some circumstances GHC does that (needs optimising, and I expect the number of types involved mustn't be too large). Here we confront it with what is basically an inhomogeneous list, so in each invocation of g (f x), it can be needed at an arbitrary type satisfying the constraints, so the computation cannot be lifted outside the map (technically, the compiler could still build a cache of the values at each used type, so it would be evaluated only once per type, but GHC doesn't, in all likelihood it wouldn't be worth the trouble).
Monomorphic expressions need only be evaluated once, they can be shared. Whether they are is up to the implementation; by purity, it doesn't change the semantics of the programme. If the expression is bound to a name, in practice you can rely on it being shared, since it's easy and obviously what the programmer wants. If it isn't bound to a name, it's a question of optimisation. With the bytecode generator or without optimisations, the expression will often be evaluated repeatedly, but with optimisations repeated evaluation would indicate a compiler bug.
Polymorphic expressions must be evaluated at least once for every type they're used at, but with optimisations, when GHC can see that it may be used multiple times at the same type, it will (usually) still be shared for that type during a larger computation.
Bottom line: Always compile with optimisations, help the compiler by binding expressions you want shared to a name, and give monomorphic type signatures where possible.
Your examples are indeed quite different.
In the first example, the argument to map is g (f x) and is passed once to map most likely as partially applied function.
Should g (f x), when applied to an argument within map evaluate its first argument, then this will be done only once and then the thunk (f x) will be updated with the result.
Hence, in your first example, f xwill be evaluated at most 1 time.
Your second example requires a deeper analysis before the compiler can arrive at the conclusion that (f x) is always constant in the lambda expression. Perhaps it will never optimize it at all, because it may have knowledge that trace is not quite kosher. So, this may evaluate 4 times when tracing, and 4 times or 1 time when not tracing.
This is really dependent on GHC's optimizations, as you've been able to tell.
The best thing to do is to study the GHC core that you get after optimizing the program. I would look at the generated Core and examine whether f x had its own let statement outside the map or not.
If you want to be sure, then you should factor f x out into its own variable assigned in a let, but there's not really a guaranteed way to figure it out other than reading through Core.
All that said, with the exception of things like trace that use unsafePerformIO, this will never change the semantics of your program: how it actually behaves.
In GHC without optimizations, the body of a function is evaluated every time the function is called. (A "call" means the function is applied to arguments and the result is evaluated.) In the following example, f x is inside a function, so it will execute each time the function is called.
(GHC may optimize this expression as discussed in the FAQ [1].)
let f x = trace "!" $ zip x x
x = "abc"
in map (\i -> lookup i (f x)) "abcd"
However, if we move f x out of the function, it will execute only once.
let f x = trace "!" $ zip x x
x = "abc"
in map ((\f_x i -> lookup i f_x) (f x)) "abcd"
This can be rewritten more readably as
let f x = trace "!" $ zip x x
x = "abc"
g f_x i = lookup i f_x
in map (g (f x)) "abcd"
The general rule is that, each time a function is applied to an argument, a new "copy" of the function body is created. Function application is the only thing that may cause an expression to re-execute. However, be warned that some functions and function calls do not look like functions syntactically.
[1] http://www.haskell.org/haskellwiki/GHC/FAQ#Subexpression_Elimination

Resources