Can I write a duplicate function which doesn't share?

By a duplicate function I mean something like this:

duplicate :: a -> (a,a)
duplicate x = (x,x)

But I want a version of this function which explicitly doesn’t share computations between the two copies. As an example, here is a (highly artificial) example how this might be used:

foo :: [Int] -> IO ()
foo xs = do
  let (zs, vs) = duplicate xs
  print (zs !! 1000000)
  expensive
  print (vs !! 1000001)

bar :: IO ()
bar = foo [1..]

And this should behave differently than the following version:

foo' :: [Int] -> IO ()
foo' xs =
  print (xs !! 1000000)
  expensive
  print (xs !! 1000001)

I want the garbage collector to be able to free the list data structure during the computation of expensive, which only works if the computation isn’t shared between zs and vs.

I assume that if it works at all that I have to use some GHC primitives? I do not have any “business need” for this, it is more curiosity about whether this would work in Haskell at all. Essentially, it is a simulation of call-by-name in a call-by-need language. (Edit: Changed the example to avoid CSE)

2 Likes

You may be interested in dup – Explicit un-sharing in Haskell by @nomeata. I think oneShot is the implemented version of noupdate mentioned at the end of the slides.

By the way, I’m completely against programming in this style :slight_smile: I can’t imagine it can lead anywhere other than madness. But I think it’s fair to share the state of the art, and this is the latest on the subject that I know of.

4 Likes

Also see GitHub - well-typed/dupIO and the corresponding presentation at the HIW for an excellent recent overview of this topic:

3 Likes

Edit: doesn’t work because GHC is too smart!

You could have foo have type:

foo :: (() -> [Int]) -> IO ()

values in Haskell are lazy, but shared. This function takes in a lazy-but-unshared value.

Only downside is that the function user has to ensure that the () -> [Int] they provide wasn’t defined in a sharing way (e.g. let foo = [1, 2, 3] in \() -> foo would defeat the point)

1 Like

@santiweight Even in that case, Haskell will still often share the value “behind” the closure, eg via (but not just via) -ffull-laziness which is enabled by -O. It is non-trivial to prevent GHC from sharing things behind your back, see the links above.

3 Likes

Thanks for the answers, they were extremely helpful :slight_smile: I have read Joachim’s paper [1207.2017] dup -- Explicit un-sharing in Haskell and have also watched the HIW presentation by Edsko. What I had in mind is something like what Joachim calls deepDup in his paper, and which recursively copies the heap reachable from its argument. The new version of ghc-dup, i.e. dupIO only seems to provide the shallow version dup, where we have to be more careful with the arguments we pass to it.

By the way, I’m completely against programming in this style :slight_smile:

Yes, me too. But I was thinking about ways to bundle this up in novel combinators. The fundamental abstraction should probably be a comonoid, i.e. the following class:

class Comonoid a where
  duplicate :: a %1 -> (a,a)
  drop :: a %1 -> ()

Comonoids are not so strange, they correspond to Drop + Clone in Rust.

Also see GitHub - well-typed/dupIO and the corresponding presentation at the HIW for an excellent recent overview of this topic:

Thanks, I really enjoyed that excellent talk. What I took from it is the insight that we have two kinds of non-strict data: Data structures and control structures, and we only want to share data structures, but not control structures. Or in other words, control structures should be call-by-name, and (non-strict) data structures should be call-by-need. Edsko describes this at the end of his talk, when he mentions that some types should be marked as “non-updateable”. And Joachim’s remark that this could be encoded as an additional Levity also lines up with my understanding that I got from the Kinds are calling conventions and Beyond polarity papers.

3 Likes

And indeed, there are classes Consumable and Dupable in linear-base.

4 Likes

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.

6 Likes

@DavidB perhaps I haven’t had enough coffee yet but … why would you need/want such a construction?

1 Like

Sorry, I didn’t provide a real motivation above. The short answer is that this helps avoid certain space leaks which are due to call-by-need evaluation. Call-by-need is not a pure optimization, it is a space-vs-time trade-off: I have the guarantee that I don’t evaluate the same thunk multiple times (better in time), but I have to use memory to store the evaluated thunk (worse in space). In most cases the trade-off is a good one, but sometimes call-by-name is vastly superior. This can be the case for those algorithms which uses a lazy data structure which represents some enormous search space, and which use another algorithm to explore that search space. In that case it can be essential to free the memory of some explored region of the search space from time to time, and not hold on to it, otherwise you run out of memory. Edsko de Vries, in the talk linked above, has a different use case for the conduit library, where call-by-need also introduces space leaks.

4 Likes

thank you, that’s a great explanation.

Can inline do the trick ?

Note that just as in very specific scenarios it’s better to discard the value and stick to the unevaluated call-by-name closure, the converse can also be true. And often it is! I conjecture that call-by-name will in fact introduce more space leaks than it will fix compared to call-by-need, because closures tend to keep alive a large residency, whereas their values are flat (if evaluated deeply, of course).

Space leaks tend to occur when a closure with a huge transitive residency could be evaluated into a small value. Call-by-name fosters representing a computation as the former, call-by-value as the latter. Call-by-need will switch to the latter after the first evaluation. So whenever call-by-value would be preferable to call-by-need, you definitely would be even worse off with call-by-name.
I think Edsko’s use case is sufficiently different to that, but I don’t think unsharing is a silver bullet to get rid of space leaks.

2 Likes

Inlining a thunk destroys sharing, so yes, it would do the trick. Of course, telling GHC to inline the thing you want duplicated and nothing else is another story; plus GHC would have to make sure that it doesn’t apply Common Subexpression Elimination to the inlined occurrences, reversing the transformation.

I don’t think duplication by inlining is feasible.

1 Like

I think avoiding that is as simple as adding a CONLIKE pragma