RE: [Haskell-cafe] Re: FPS: Finalizers not running (was Memory usageoutside of the Haskell heap)

Finalizers aren't guaranteed to be run. In particular, if the main thread exits, then we don't run any outstanding finalizers. This change was made recently, but it turned out that even prior to 6.4 we couldn't guarantee to run all outstanding finalizers. Does this explain it, or is there something else going on? BTW, when you addForeignPtrConcFinalizer to a ForeignPtr created with mallocForeignPtr, you're *creating* a finalizer, it doesn't have one to start with. It's pretty expensive to do this. Cheers, Simon On 07 November 2005 01:42, Donald Bruce Stewart wrote:
joelr1:
David,
I followed your suggestion and I think the finalizers for FPS are not running.
Here are some experiments. Sometimes I can get the finalizers to run as expected, but only when putting memory pressure on the Haskell heap with normal haskell values. Works with 6.4.1 and 6.5 on OpenBSD or Linux.
So here we generate a bunch of lists inside Haskell, then pack them. Our finalisers get run nicely as expected:
import qualified Data.FastPackedString as P import Foreign.Concurrent import Data.Word import Data.Char
data_ = [ replicate 5000 i | i <- [1..100] ] :: [[Word8]]
main = do foo data_ putStrLn ""
foo [] = return () foo (x:xs) = do let fps = P.packWords x installFinalizer fps putStr "." foo xs
installFinalizer fps@(P.PS fp _ _) = addForeignPtrFinalizer fp $ putStr (show.ord.P.head $ fps)
pill00$ ./a.out 100
..................................................1234567891011121314151 617181920212223242526272829303132333435363738394041424344454647484950... ........................................51525354555657585960616263646566 6768697071727374757677787980818283848586878889909192.......
Now, if we instead allocate only outside the Haskell heap (with an mmap packed string), then we see something different:
import qualified Data.FastPackedString as P import Foreign.Concurrent import Data.Word import Data.Char
main = do foo 100 putStrLn ""
foo 0 = return () foo n = do fps <- P.mmapFile "/home/dons/tmp/tests/128k" installFinalizer fps putStr "." foo (n-1)
installFinalizer fps@(P.PS fp _ _) = addForeignPtrFinalizer fp $ putStr (show.ord.P.head $ fps)
No finalisers (even though more data is allocated)!
$ ./a.out
........................................................................ ..............
The GHC rts doesn't know how big the packed string is. It just sees the few bytes of the packed string (as dcoutts pointed out on irc).
Strangely, the same effect is seen with P.readFile, which (from darcs) allocates as so:
mallocForeignPtr :: Int -> IO (ForeignPtr Word8) mallocForeignPtr l = when (l > 1000000) performGC >> mallocForeignPtrArray l
where here mallocForeignPtrArray ends up calling GHC.Prim.newPinnedByteArray# (i.e. on the Haskell heap). Hmm. I don't understand that then, as the memory is in the Haskell heap, yet still no finalisers are run.
If we do something expensive with the packed string, then finalizers get run:
foo n = do fps <- P.readFile "/home/dons/tmp/tests/128k" installFinalizer fps
-- unpack the string into a normal Haskell list: forkIO (Control.Exception.evaluate ((length . P.unpack) fps) >> return ()) putStr "." foo (n-1)
Also interestingly, calling unsafeFinalize didn't help.
Simon, any thoughts on this? Is there some way we can ensure memory outside the Haskell heap gets counted for its full weight? Also, why don't we see any finalizers run with the pinned arrays?
-- Don _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

simonmar:
Finalizers aren't guaranteed to be run. In particular, if the main thread exits, then we don't run any outstanding finalizers. This change was made recently, but it turned out that even prior to 6.4 we couldn't guarantee to run all outstanding finalizers.
Does this explain it, or is there something else going on?
BTW, when you addForeignPtrConcFinalizer to a ForeignPtr created with mallocForeignPtr, you're *creating* a finalizer, it doesn't have one to start with. It's pretty expensive to do this.
Ah, right, I see. It's: mallocForeignPtr = doMalloc undefined where doMalloc :: Storable b => b -> IO (ForeignPtr b) doMalloc a = do IO $ \s -> case newPinnedByteArray# size s of { (# s, mbarr# #) -> (# s, ForeignPtr (byteArrayContents# (unsafeCoerce# mbarr#)) (MallocPtrNoFinalizer mbarr#) #) } where (I# size) = sizeOf a So the GC will take care of these thingies? Now, this probably means that the problem is somewhere else in Joelr's code. -- Don
participants (2)
-
dons@cse.unsw.edu.au
-
Simon Marlow