
Hello, While working in the StaticPointers language extension [1], we found we have some unusual CAFs which can be accessed after some periods of time where there is no reference to them. For instance, the following program when compiled contains no reference to `g`. `g` is actually looked up at runtime in symbol tables via the call to `deRefStaticPtr`. g :: String g = "hello" main = deRefStaticPtr (static g) >>= putStrLn Desugars to: g :: String g = "hello" main = deRefStaticPtr (StaticPtr (StaticName "" "Main" "g")) >>= putStrLn In principle, there is nothing stopping the garbage collector from reclaiming the closure of `g` before it is dynamically looked up. We are considering using StablePtrs to preserve `g`. So the code desugars instead to: g :: String g = "hello" main = deRefStaticPtr (let x = StaticPtr (StaticName "" "Main" "g") in unsafePerformIO $ newStablePtr g >> return x ) >>= putStrLn This solution could be temporal though, until we implement the so called static pointer table, which would keep the values alive. Would you have any comments about such a solution or maybe would you advice some other alternative? Thanks, Facundo [1] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers

Hi Facundo, You are completely right, the CAF named "g" might be accessed at any time during the program execution. Parallel Haskell systems with distributed heap (and runtime-supported serialisation) need to keep all CAFS alive for this reason. Some comments inline along your mail:
While working in the StaticPointers language extension [1], we found we have some unusual CAFs which can be accessed after some periods of time where there is no reference to them.
For instance, the following program when compiled contains no reference to `g`. `g` is actually looked up at runtime in symbol tables via the call to `deRefStaticPtr`. g :: String g = "hello"
main = deRefStaticPtr (static g) >>= putStrLn
The bad scenario is certainly one where CAF g (a static thunk) is evaluated during execution (i.e. turned into an indirection into the heap), and then garbage-collected, as it might not be referenced by any (runnable) thread. This GC does not revert the indirection into a thunk. Why should it, there are no references to it, right? ;-) So technically, your example might need to involve using g (and forceful GC at a certain point during execution): main = putStrLn g >> performGC >> deRefStaticPtr (static g) >>= putStrLn
Desugars to:
g :: String g = "hello"
main = putStrLn g >> performGC >> deRefStaticPtr (StaticPtr (StaticName "" "Main" "g")) >>= putStrLn
During performGC, there would be no reference to g from any thread's stack. I am of course assuming that g is indeed a thunk, and not statically evaluated to a string during compilation (I am unsure whether GHC would do that).
In principle, there is nothing stopping the garbage collector from reclaiming the closure of `g` before it is dynamically looked up.
Maybe a stupid question, sorry: The RemoteTable generated using template-haskell in CH without XStaticPointers would keep CAFs alive. So the XStaticPointers extension does not entail using such a table?
We are considering using StablePtrs to preserve `g`. So the code desugars instead to:
g :: String g = "hello"
main = deRefStaticPtr (let x = StaticPtr (StaticName "" "Main" "g") in unsafePerformIO $ newStablePtr g >> return x ) >>= putStrLn
Another question: Would it be sufficient to desugar "static g" to g `seq` StaticPtr(StaticName "" "Main" "g") instead of introducing a stable ptr and all that? AFter all, g is a CAF, so it is anyway "stable" in some sense, as long as it is alive. However, I conjecture that this only fixes the one-node test, not the actual use case (sending "static" stuff over the wire). Finally, there is a flag keepCAFs in the runtime which you can set to secure the CAFs for the entire run. The parallel runtimes for Eden and GUM (as well as my "packman" serialisation) do this. Yes, obviously, this opens a memory leak. It would be nice to not "keep" but "revert" the CAFs (ghci does that) but on a "by-need" basis when a simple GC cannot reclaim enough space; this would plug the mem.leak. This requires a modification to the GHC runtime system, and it is unclear _which_ CAFs to prefer when starting to revert. But I think it would be a more generally useful feature. However, this discussion (runtime/GC features) leads us straight out of the design goals of "-XStaticPointers", I guess... Best regards, Jost

So technically, your example might need to involve using g (and forceful GC at a certain point during execution)
Good observation.
Maybe a stupid question, sorry: The RemoteTable generated using template-haskell in CH without XStaticPointers would keep CAFs alive. So the XStaticPointers extension does not entail using such a table?
That's correct. The extension is a substitute for the remote table. In addition, it has the compiler do what remote tables demanded from the user: * adding functions to the remote table before they are looked up, * collecting the table pieces from the various modules into a global table.
Another question: Would it be sufficient to desugar "static g" to g `seq` StaticPtr(StaticName "" "Main" "g") instead of introducing a stable ptr and all that?
This keeps g alive only while the expression is not evaluated to HNF. The solution I proposed is flawed as well, since it relies on the desugared static form being evaluated to HNF for the CAF to be referenced with a StablePtr. Anyway, after this much time we figured out how to implement the static pointer table.
Finally, there is a flag keepCAFs in the runtime which you can set to secure the CAFs for the entire run. The parallel runtimes for Eden and GUM (as well as my "packman" serialisation) do this.
Good to know about that. Thank you, Facundo
AFter all, g is a CAF, so it is anyway "stable" in some sense, as long as it is alive.
However, I conjecture that this only fixes the one-node test, not the actual use case (sending "static" stuff over the wire).
Finally, there is a flag keepCAFs in the runtime which you can set to secure the CAFs for the entire run. The parallel runtimes for Eden and GUM (as well as my "packman" serialisation) do this.
Facundo
On Tue, Nov 18, 2014 at 1:20 PM, Jost Berthold
Hi Facundo,
You are completely right, the CAF named "g" might be accessed at any time during the program execution. Parallel Haskell systems with distributed heap (and runtime-supported serialisation) need to keep all CAFS alive for this reason.
Some comments inline along your mail:
While working in the StaticPointers language extension [1], we found we have some unusual CAFs which can be accessed after some periods of time where there is no reference to them.
For instance, the following program when compiled contains no reference to `g`. `g` is actually looked up at runtime in symbol tables via the call to `deRefStaticPtr`. g :: String g = "hello"
main = deRefStaticPtr (static g) >>= putStrLn
The bad scenario is certainly one where CAF g (a static thunk) is evaluated during execution (i.e. turned into an indirection into the heap), and then garbage-collected, as it might not be referenced by any (runnable) thread. This GC does not revert the indirection into a thunk. Why should it, there are no references to it, right? ;-)
So technically, your example might need to involve using g (and forceful GC at a certain point during execution):
main = putStrLn g >> performGC >> deRefStaticPtr (static g) >>= putStrLn
Desugars to:
g :: String g = "hello"
main =
putStrLn g >> performGC >>
deRefStaticPtr (StaticPtr (StaticName "" "Main" "g")) >>= putStrLn
During performGC, there would be no reference to g from any thread's stack. I am of course assuming that g is indeed a thunk, and not statically evaluated to a string during compilation (I am unsure whether GHC would do that).
In principle, there is nothing stopping the garbage collector from reclaiming the closure of `g` before it is dynamically looked up.
Maybe a stupid question, sorry: The RemoteTable generated using template-haskell in CH without XStaticPointers would keep CAFs alive. So the XStaticPointers extension does not entail using such a table?
We are considering using StablePtrs to preserve `g`. So the code desugars instead to:
g :: String g = "hello"
main = deRefStaticPtr (let x = StaticPtr (StaticName "" "Main" "g") in unsafePerformIO $ newStablePtr g >> return x ) >>= putStrLn
Another question: Would it be sufficient to desugar "static g" to g `seq` StaticPtr(StaticName "" "Main" "g") instead of introducing a stable ptr and all that? AFter all, g is a CAF, so it is anyway "stable" in some sense, as long as it is alive.
However, I conjecture that this only fixes the one-node test, not the actual use case (sending "static" stuff over the wire).
Finally, there is a flag keepCAFs in the runtime which you can set to secure the CAFs for the entire run. The parallel runtimes for Eden and GUM (as well as my "packman" serialisation) do this.
Yes, obviously, this opens a memory leak. It would be nice to not "keep" but "revert" the CAFs (ghci does that) but on a "by-need" basis when a simple GC cannot reclaim enough space; this would plug the mem.leak. This requires a modification to the GHC runtime system, and it is unclear _which_ CAFs to prefer when starting to revert. But I think it would be a more generally useful feature. However, this discussion (runtime/GC features) leads us straight out of the design goals of "-XStaticPointers", I guess...
Best regards, Jost _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

Isn't it this simple: the Static Pointer Table must be a source of roots for the garbage collector. Of course! An item in the SPT may be looked up at any time. Easy. What am I missing? I'm deeply suspicious of any solution that involves a call to performGC. That smells wrong. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of | Facundo Domínguez | Sent: 18 November 2014 00:44 | To: ghc-devs@haskell.org | Subject: Fwd: Garbage collection | | Hello, | While working in the StaticPointers language extension [1], we | found we have some unusual CAFs which can be accessed after some | periods of time where there is no reference to them. | | For instance, the following program when compiled contains no | reference to `g`. `g` is actually looked up at runtime in symbol | tables via the call to `deRefStaticPtr`. | | g :: String | g = "hello" | | main = | deRefStaticPtr (static g) >>= putStrLn | | Desugars to: | | g :: String | g = "hello" | | main = | deRefStaticPtr (StaticPtr (StaticName "" "Main" "g")) >>= putStrLn | | In principle, there is nothing stopping the garbage collector from | reclaiming the closure of `g` before it is dynamically looked up. | | We are considering using StablePtrs to preserve `g`. So the code | desugars instead to: | | g :: String | g = "hello" | | main = | deRefStaticPtr (let x = StaticPtr (StaticName "" "Main" "g") | in unsafePerformIO $ newStablePtr g >> return | x | ) >>= putStrLn | | This solution could be temporal though, until we implement the so | called static pointer table, which would keep the values alive. | | Would you have any comments about such a solution or maybe would you | advice some other alternative? | | Thanks, | Facundo | | [1] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers | _______________________________________________ | ghc-devs mailing list | ghc-devs@haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs

On 18 November 2014 16:59, Simon Peyton Jones
Isn't it this simple: the Static Pointer Table must be a source of roots for the garbage collector. Of course! An item in the SPT may be looked up at any time.
As Facundo says, the existence of the SPT would solve everything. But we haven't quite figured out how to create a simple SPT yet, so were wondering whether there is an existing generic mechanism to register new GC roots. I guess there is no better solution but to just create an SPT, even if we don't yet have TypeRep's to put in it. With an SPT, and under the assumption of everyone sharing the same binary in the distributed system, there will be no need to hold on to *all* CAF's - just the ones that are known to have a StaticPointer created for them at compile time.

I'm reluctant to invest much effort in a hack, when we know we are going to create an SPT anyway. Let's just go for it! Even if there are no TypeReps in it yet.
Actually, I think that each entry in the SPT should have just two fields: something like
Key, Value
where "Key" is whatever we use as the "stable name" for the static value: a string, or something like that.
The "Value" is a full Haskell value, just a pointer into the heap (these are the new GC roots). The value has type Dynamic, or something very like it:
data Dynamic where
MkDyn :: TTypeRep a -> a -> Dynamic
Maybe the library Dynamic isn't quite what we need; e.g we may want to include the Key too:
data SptEntry where
SPT :: String -> TTypeRep a -> a -> SptEntry
But regardless, the SPT itself is a simple key/value table, and all the interesting structure in in the Values in Haskell-land.
Now all we need is
- To build top-level bindings for the SPT Entries.
These bindings are presumably created by the desugarer,
as it desugars uses of 'static'
- To collect them in an SPT
This is presumably done in a similar way to the mkModuleInit stuff
in StgCmm.codeGen
Simon
| -----Original Message-----
| From: 0xbadcode@gmail.com [mailto:0xbadcode@gmail.com] On Behalf Of
| Mathieu Boespflug
| Sent: 18 November 2014 18:03
| To: Simon Peyton Jones
| Cc: Facundo Domínguez; ghc-devs@haskell.org; Mathieu Boespflug
| Subject: Re: Garbage collection
|
| On 18 November 2014 16:59, Simon Peyton Jones

On 18/11/2014 18:03, Mathieu Boespflug wrote:
On 18 November 2014 16:59, Simon Peyton Jones
wrote: Isn't it this simple: the Static Pointer Table must be a source of roots for the garbage collector. Of course! An item in the SPT may be looked up at any time.
As Facundo says, the existence of the SPT would solve everything. But we haven't quite figured out how to create a simple SPT yet, so were wondering whether there is an existing generic mechanism to register new GC roots.
Yes - the generic mechanism is StablePtrs, so you're on the right lines. Even when you have an SPT you'll probably need to make a StablePtr to it (though I haven't been following the discussion so just ignore me if I'm wrong here). Cheers, Simon
I guess there is no better solution but to just create an SPT, even if we don't yet have TypeRep's to put in it.
With an SPT, and under the assumption of everyone sharing the same binary in the distributed system, there will be no need to hold on to *all* CAF's - just the ones that are known to have a StaticPointer created for them at compile time. _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs
participants (5)
-
Facundo Domínguez
-
Jost Berthold
-
Mathieu Boespflug
-
Simon Marlow
-
Simon Peyton Jones