This is a write-up of a rough idea that Andres Löh and me had at ICFP 2016 in order to address some Real World problems Andres noticed and that are currently hard to avoid.
The goal is to give the user more control about expressions that the compiler would like to float out (or CSE), but the programmer knows better. Example (assume no list fusion exists):
enum xs = zip [1..] xs
This leads to a horrible space leak, as GHC will float out [1..] to the top.
Our idea is to have a magic function nofloat :: a -> a (magic in the same sense as inline and lazy) that the programmer would use here:
enum xs = zip (nofloat [1..]) xs
With these effects:
Sub expressions are not floated out of a nofloat.
An expression of the form nofloat e would not be floated beyond the innermost enclosing lambda.
Two expressions of the form nofloat e would not be commoned up by CSE.
This way, unwanted sharing is prevented.
In contrast to a hypothetical veryCheap function, it does not mean that the compiler should float it into lambda (no unwanted duplication either).
Two open questions (among many others, I am sure:)
Likely, rule matching should look through nofloat. At least in this example (and similar ones like map (nofloat [1..]), the rules in question will avoid the spaceleaks).
Possibly, nothing should be floated (inlined) into a nofloat. Rationale: Assume the library is changed so that
Then zip [fib 1000..] would be rewritten by the inliner to zip (let x = fib 1000 in (nofloat [x..])). Moving the fib 1000 into the nofloat would change the behaviour in a possibly surprising way.
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
That all looks possible. Since nofloat does several things, it may not be long before people start asking for variants that do some combination of its properties. But I guess we can jump that bridge if we come to it.
It would be useful to give some compelling use-cases.
Can I suggest a closely related idea, and also related to #9520 (closed)
data Pipe i o r = Yield o {-# NOUPDATE #-} (Pipe i o r)
This says we'll never do thunk updates on that field in that constructor. So similar idea (I believe) to oneShot lambdas.
Indeed we might need both no update on fields and oneShot, I'm not sure, e.g.:
data Pipe i o r = Yield o {-# NOUPDATE #-} (Pipe i o r) | Await {-# NOUPDATE #-} (Either r i -> Pipe i o r)-- smart constructor:await f = Await (GHC.Magic.oneShot f)
What's all this for? For avoiding treating these control structures as data structures (which is what #9520 (closed) is all about).
Right, so a lot of the thinking that led to this ticket came from trying to understand memory leaks in conduit code. See my recent blog post http://www.well-typed.com/blog/2016/09/sharing-conduit/ where these issues are described in great detail; this should also serve, I hope, as one "compelling use case".
That said, I like the idea of a "noupdate" much better than a "nofloat". It would seem to me that its semantics would be easier to specify; and if it means I don't have to think so hard about what exactly the optimizer is doing to my code in order to understand why I do or do not have a memory leak, that would very welcome.
I really like @duncan 's suggestion of having a type annotation on a type; though we might also want some adhoc way of saying "make this thunk not-updateable". An easyish experiment perhaps might be to declare a magic datatype
dataDontUpdatea=DontUpdatea
with the property that any code that looks at the thunk in the payload of DontUpdate doesn't cause that thunk to be updated. Then in @duncan 's example we could define
dataPipeior=Yieldo(DontUpdate(Pipeior))
That said, I'm not sure exactly what DontUpdate should do for the lambda; but this is a question about @duncan's proposal too. I think what we want to happen is that the thunks in the function closure never get updated (this, in a nutshell, is what is causing memory leaks in conduit code; see the blog post); but that's already more magical than just saying "don't update this thunk".
I think that "noupdate" would require some careful thought. What if I say
f x = if ... then Yield blah x else ...
Then the "noupdate" second field of Yield is just the parameter to f. Does the caller have to know not to build an updatable thunk. And why is updating so bad?
(Confession: I have not yet read Edsko's post. But I it should be possible to give a crisp explanation of what any language feature does in a standalone way.)
Right, this is an initial idea and hasn't been fleshed out. Thanks for the probing example :-)
So the intention is that it's a purely local thing. So in that example, the answer is no, we do not expect a caller far away to have to know anything. The idea is that evaluating "via" the noupdate field should not perform thunk updates, but I appreciate that may not match how thunk construction and update works.
So how about something like this...
Suppose the primitive is not on fields, but on let. This is by analogy with strict let !_ = versus strict constructor fields. The primitive with strictness is at use sites and a convenience for systematic use we can push it to constructor fields, which is defined in terms of constructor wrappers.
So suppose the primitive is let {-# NOUPDATE #-} x = ..., and so then the Yield constructor above could perhaps be defined with a wrapper like
So in your f x example above then this would do very little (and indeed we'd want it to do precisely nothing different to the usual, by shorting out the extra let indirection). But if things are defined with Yield (expr) or locally ghc decides to float/push things in, then the expression would end up in the let {-# NOUPDATE #-} x' = ... and so there would be an effect.
I'm very glad to see full laziness getting some attention. I've been aware of its deleterious effects for some time and have tried to spread awareness of it:
The full laziness transformation causes a lot of headaches and something really needs to be done about it.
However I do not think this suggestion is the right approach. Why not tweak the transformation so that it only fires in cases that are guaranteed not to lead to memory leaks? That could be as simple as only hoisting bindings of monomorphic non-recursive datatypes. The proposed nofloat keyword is just adding additional complexity over a transformation which itself is introducing too much complexity. I'm very concerned about the idea.
I think that "noupdate" would require some careful thought. What if I say
f x = if ... then Yield blah xelse ...
Then the "noupdate" second field of Yield is just the parameter to f. Does the caller have to know not to build an updatable thunk.
I guess we would instruct the demand analysis to believe that Yield has strictness signature <L,U><L,1*U> and thus this once-used information will be propagated, at least to the extent possible.
I'm very glad to see full laziness getting some attention (...) I have even asked whether it is an optimization worth performing at all, though I conclude that it is:
However I do not think this suggestion is the right approach. (...) The proposed nofloat keyword is just adding additional complexity over a transformation which itself is introducing too much complexity. I'm very concerned about the idea.
I agree that it would be preferable not to "program the optimizer" when writing Haskell code. That's another reason in fact why I prefer noupdate over nofloat, beacuse actually noupdate goes beyond full laziness. Consider this example from the blog post:
This program has a memory leak, but it's nothing to do with full laziness here. Now admittedly we could turn this into a full laziness issue by giving the argument to retry a dummy unit argument or something like that, so that we write
or something like that, but then you would have to do that in every single function that duplicates IO actions (think forever, replicateM_, etc.) Instead, we could mark that list as noupdate and the memory leak would be gone.
Fair enough, that's an easier workaround. But the idea is to have something a little more compositional. For example, in the case of conduits, we probably never want to share a conduit value. So it would be great if we could annotate the conduit constructors with a noupdate annotation, and then users of the conduit library don't have to worry about this problem anymore. After all, in the list example, it's not obvious that
main::IO()main=retry$runConduitsomeConduit
has a space leak; even less so when that retry and the runConduit are in different places:
The situation really is very close to strictness; do we want to make sure every single function using a datatype has the right seqs in the right place, or we just put some strictness annotations on the datatype?
Edsko, I'm a bit puzzled. For the case of conduits, isn't it enough to hide things behind lambdas in the definition of the Pipe type?
Wren, sure, but Edsko's original claim is that this isn't a full laziness issue. My example brings it back to being a full laziness issue indeed. My contention is that even given Edsko's example it still makes more sense to fix the full laziness transformation than add a magic word.