I think oneShot
is a bit different to noupdate
, because it needs to be applied to a function whose body GHC will no longer be prone to float stuff out of (still, it well could). E.g.,
oneShot $ \() -> [1..100]
Without oneShot
, GHC will just float out the list. With oneShot
, it won’t, because there is no benefit to: The user said that the lambda will only be entered at most once. If you had written
f y =
let x = fib y in
let g = oneShot $ \n -> [1..n+x] in
g 0 ++ g 1 ++ g 2
Then GHC would also be allowed to float fib y
inside the lambda, thus accidentally duplicating more work than the programmer intended to.
If we instead had
f x = g x
where
g 0 = oneShot $ \() -> [1..x]
g n = g (n-1) () ++ g (n-2) ()
Then I think that GHC will float the list out of g
where it is evaluated at most once per invokation of f
.
So oneShot
is neither more general nor more specific than noupdate
.
It is notoriously hard to identify and maintain all the places where GHC might float stuff out in this manner (after all it’s one of the tenets of laziness to float freely), which is perhaps the reason there is no noupdate
to this day. Not sure what became of Joachim’s work.
The way I’d work around this is by defining
noupdate :: ((forall a. a -> a) -> r) -> r
noupdate f = f id
{-# OPAQUE noupdate #-}
foo n = do
let xs = noupdate (\hide -> [1..hide n])
print (xs !! 1000000)
expensive
print (xs !! 1000001)
This in itself only introduces a float barrier for the expression [1..n]
wherever hide
is used, so the user eplicitly declares which parts of a computation should not be shared, rather than a wildcard "duplicate xs
", which might transitively duplicate the whole heap.
Then in CorePrep you’d see something like
let f = {...} \r [hide] enumFromTo ... hide ...
let x = {f} \u noupdate f in
...
Syntax: {f}
lists f
as the free variable of x
's closure, \r
means “reentrant” (think: function), \u
means “updateable” (think: thunk), [hide]
is a singleton list of lambdas.
To get the desired effect, we need GHC to detect \u noupdate f
and turn it into \s f id
, where \s
means “single-entry thunk” (which is essentially the same as a function, \r
, only that we may detect <<loop>>
s if we wanted to. Perhaps \r
is a better fit because we sometimes validate \s
by counting the number of actual entries, which will be more than once for serious use of noupdate
).
Should not be too hard to implement! Just needs someone dedicated to baby-sit the GHC proposal.