Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Miguel Mitrofanov
Hmm, interesting. Seems like I have to take a closer look at GHC's garbage collection. Thanks! On 8 Jan 2010, at 00:53, Edward Kmett wrote: That is kind of what I thought you were doing. Retooling to see if we can get any better performance out of collecting, it seems that System.Mem.Perfo

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Edward Kmett
That is kind of what I thought you were doing. Retooling to see if we can get any better performance out of collecting, it seems that System.Mem.PerformGC does a foreign call out to performMajorGC to ask for a global collection. But I would hazard that you might be able to get most of the benefit

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Miguel Mitrofanov
I liked it too. Seems like I have to show some real code, and my apologies for a long e-mail. Well, that's what I'm actually trying to do and what I've managed to achieve so far. > module Ask where > import Control.Monad > import Data.IORef > import Data.Maybe > import System.IO.Unsafe -- Y

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Edward Kmett
Thats a shame, I was rather fond of this monad. To get that last 'True', you'll really have to rely on garbage collection to approximate reachability for you, leaving the weak reference solution the best you can hope for. -Edward Kmett On Thu, Jan 7, 2010 at 12:39 PM, Miguel Mitrofanov wrote: >

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Miguel Mitrofanov
Damn. Seems like I really need (True, False, True) as a result of "test". On 7 Jan 2010, at 08:52, Miguel Mitrofanov wrote: Seems very nice. Thanks. On 7 Jan 2010, at 08:01, Edward Kmett wrote: Here is a slightly nicer version using the Codensity monad of STM. Thanks go to Andrea Vezzosi

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
Seems very nice. Thanks. On 7 Jan 2010, at 08:01, Edward Kmett wrote: Here is a slightly nicer version using the Codensity monad of STM. Thanks go to Andrea Vezzosi for figuring out an annoying hanging bug I was having. -Edward Kmett {-# LANGUAGE Rank2Types, GeneralizedNewtypeDeriving, De

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Edward Kmett
Here is a slightly nicer version using the Codensity monad of STM. Thanks go to Andrea Vezzosi for figuring out an annoying hanging bug I was having. -Edward Kmett {-# LANGUAGE Rank2Types, GeneralizedNewtypeDeriving, DeriveFunctor #-}module STMOracle( Oracle, Ref, newRef, readRef, writeR

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Edward Kmett
I don't believe you can get quite the semantics you want. However, you can get reasonably close, by building a manual store and backtracking. {-# LANGUAGE Rank2Types #-} -- lets define an Oracle that tracks whether or not you might need the reference, by backtracking. module Oracle ( Oracle, R

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
On 6 Jan 2010, at 23:21, Edward Kmett wrote: You probably just want to hold onto weak references for your 'isStillNeeded' checks. That's what I do now. But I want to minimize the network traffic, so I want referenced values to be garbage collected as soon as possible - and I couldn't fin

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Edward Kmett
You probably just want to hold onto weak references for your 'isStillNeeded' checks. Otherwise the isStillNeeded check itself will keep you from garbage collecting! http://cvs.haskell.org/Hugs/pages/libraries/base/System-Mem-Weak.html -Edward Kmett On Wed, Jan 6, 2010 at 9:39 AM, Miguel Mitrofa

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
I'll take a look at them. I want something like this: refMaybe b dflt ref = if b then readRef ref else return dflt refIgnore ref = return "blablabla" refFst ref = do (v, w) <- readRef ref return v test = do a <- newRef "x" b <- newRef 1 c <- newRef ('z', Just

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Dan Doel
On Wednesday 06 January 2010 8:52:10 am Miguel Mitrofanov wrote: > Is there any kind of "ST" monad that allows to know if some STRef is no > longer needed? > > The problem is, I want to send some data to an external storage over a > network and get it back later, but I don't want to send unneces

[Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
Is there any kind of "ST" monad that allows to know if some STRef is no longer needed? The problem is, I want to send some data to an external storage over a network and get it back later, but I don't want to send unnecessary data. I've managed to do something like that with weak pointers, Sys