[Haskell-cafe] Re: Are handles garbage-collected?
Remi Turk
rturk at science.uva.nl
Sun Oct 24 09:29:23 EDT 2004
On Sun, Oct 24, 2004 at 02:16:50PM +0200, Peter Simons wrote:
> Tomasz Zielonka writes:
>
> > AFAIK, Handles have finalisers which close them, but I
> > don't know if GHC triggers garbage collection when file
> > descriptors run out. If not, you will have problems if
> > you manage to run out of fds between GCs.
>
> Thank you for answering.
>
> Now there is only one problem: Assuming I could _not_ use
> 'bracket', 'withFile', 'finally' or any of the other usual
> scope-guarding techniques, what would I do? (The handle has
> to be passed up to the outside of the scope in which it was
> opened.)
Refactoring comes to the mind... ;)
> If I stored the handle in an 'MVar' and attached an
> MVar-finalizer to that, would that work better? Would the
> MVar's finalizer be run any sooner than the one attached to
> the handle anyway?
Both are just finalizers, so it won't make any difference AFAICS.
> Or can I explicitly trigger garbage collection somehow? Say,
> in case I receive an exception telling me that file
> descriptors are running out? Which exception would I even
> get in this case?
>
> Peter
You could try using something like this instead of the normal
openFile:
(or make it even less portable by importing GHC.IOBase and only
retrying on ResourceExhausted)
module Main where
import IO
import System.Mem
myOpenFile path mode
= catch (openFile path mode) $ \_ -> do
putStrLn "==> Open failed. Retrying <=="
performGC
openFile path mode
open = openFile "/tmp/foo" ReadMode
myOpen = myOpenFile "/tmp/foo" ReadMode
Example:
-- Let's eat all available filedescriptors.
*Main> sequence (repeat open)
Loading package haskell98 ... linking ... done.
*** Exception: /tmp/foo: openFile: resource exhausted (Too many open files)
-- They are indeed all gone.
*Main> h <- open
*** Exception: /tmp/foo: openFile: resource exhausted (Too many open files)
-- What about performing garbage collection?
*Main> h <- myOpen
==> Open failed. Retrying <==
*Main> h
{handle: /tmp/foo}
*Main>
Groeten,
Remi
--
Nobody can be exactly like me. Even I have trouble doing it.
More information about the Haskell-Cafe
mailing list