
At least in my experience, in order to get proper resource management for things like file or database handles, you need both a close operation and a finalizer registered with the garbage collector. The former is needed so that you can create resources faster than the garbage collector freeing them. The latter is a safety net in cases where proper resource management is not follwoed (perhaps in GHCi). When the explicit close operation or the finalizer has been invoked, the object must somehow be disabled, so that further operations on it fail (otherwise, you might dereference a dangling pointer). What's the idom for implementing this in Haskell (or GHC)? It seems that a ForeignPtr cannot be written to (otherwise I'd change it to a null pointer when the resource is freed). It's also not possible to check if the finalizers have been run. Can the finalizers hold a reference to the object which in turn holds the ForeignPtr to be finalized? Or would that prevent the finalizers from running at all? Is there a way to avoid the extra level of indirection (or is GHC sufficiently smart to optimize it away)?

On Fri, 8 Oct 2010, Florian Weimer wrote:
At least in my experience, in order to get proper resource management for things like file or database handles, you need both a close operation and a finalizer registered with the garbage collector. The former is needed so that you can create resources faster than the garbage collector freeing them. The latter is a safety net in cases where proper resource management is not follwoed (perhaps in GHCi). When the explicit close operation or the finalizer has been invoked, the object must somehow be disabled, so that further operations on it fail (otherwise, you might dereference a dangling pointer).
Some open/close pairs have corresponding 'with' functions, that are implemented using Exception.bracket. You can also use them within GHCi. I think using both manual resource deallocation and finalizers makes everything more complicated and more unreliable.

* Henning Thielemann:
Some open/close pairs have corresponding 'with' functions, that are implemented using Exception.bracket. You can also use them within GHCi. I think using both manual resource deallocation and finalizers makes everything more complicated and more unreliable.
It seems that Exception.bracket does not work in all cases, see the recent "MonadCatchIO, finally and the error monad" thread. Anyway, the ability of closures (and threads) means that something like Exception.bracket does not prevent access to closed handles, so I still need an additional safety net.

On Fri, Oct 15, 2010 at 11:09 AM, Florian Weimer
* Henning Thielemann:
Some open/close pairs have corresponding 'with' functions, that are implemented using Exception.bracket. You can also use them within GHCi. I think using both manual resource deallocation and finalizers makes everything more complicated and more unreliable.
It seems that Exception.bracket does not work in all cases, see the recent "MonadCatchIO, finally and the error monad" thread.
Anyway, the ability of closures (and threads) means that something like Exception.bracket does not prevent access to closed handles, so I still need an additional safety net.
That thread is for the function "bracket" provided by the package MonadCatchIO. Control.Exception.bracket should work fine as far as I know. Antoine

On Fri, Oct 15, 2010 at 8:17 PM, Antoine Latter
On Fri, Oct 15, 2010 at 11:09 AM, Florian Weimer
wrote: * Henning Thielemann:
Some open/close pairs have corresponding 'with' functions, that are implemented using Exception.bracket. You can also use them within GHCi. I think using both manual resource deallocation and finalizers makes everything more complicated and more unreliable.
It seems that Exception.bracket does not work in all cases, see the recent "MonadCatchIO, finally and the error monad" thread.
Anyway, the ability of closures (and threads) means that something like Exception.bracket does not prevent access to closed handles, so I still need an additional safety net.
That thread is for the function "bracket" provided by the package MonadCatchIO. Control.Exception.bracket should work fine as far as I know.
I can confer that when I brought up the issue with bracket, it's only referring to the function exported by MonadCatchIO. I sure as hell hope The Control.Exception version always works properly ;). Michael

On Fri, Oct 8, 2010 at 9:39 AM, Florian Weimer
At least in my experience, in order to get proper resource management for things like file or database handles, you need both a close operation and a finalizer registered with the garbage collector. The former is needed so that you can create resources faster than the garbage collector freeing them. The latter is a safety net in cases where proper resource management is not follwoed (perhaps in GHCi). When the explicit close operation or the finalizer has been invoked, the object must somehow be disabled, so that further operations on it fail (otherwise, you might dereference a dangling pointer).
What's the idom for implementing this in Haskell (or GHC)? It seems that a ForeignPtr cannot be written to (otherwise I'd change it to a null pointer when the resource is freed). It's also not possible to check if the finalizers have been run.
Can the finalizers hold a reference to the object which in turn holds the ForeignPtr to be finalized? Or would that prevent the finalizers from running at all? Is there a way to avoid the extra level of indirection (or is GHC sufficiently smart to optimize it away)?
Have you looked at the left-fold enumerator style? It's what takusen[1,2] and it's the basis for iteratees[3]. [1] http://projects.haskell.org/takusen/ [2] http://okmij.org/ftp/Haskell/#takusen [3] http://okmij.org/ftp/Streams.html I hope that gives you food for thought, Jason

Florian Weimer wrote:
At least in my experience, in order to get proper resource management for things like file or database handles, you need both a close operation and a finalizer registered with the garbage collector. The former is needed so that you can create resources faster than the garbage collector freeing them. The latter is a safety net in cases where proper resource management is not follwoed (perhaps in GHCi). When the explicit close operation or the finalizer has been invoked, the object must somehow be disabled, so that further operations on it fail (otherwise, you might dereference a dangling pointer).
What's the idom for implementing this in Haskell (or GHC)? It seems that a ForeignPtr cannot be written to (otherwise I'd change it to a null pointer when the resource is freed). It's also not possible to check if the finalizers have been run.
Can the finalizers hold a reference to the object which in turn holds the ForeignPtr to be finalized? Or would that prevent the finalizers from running at all? Is there a way to avoid the extra level of indirection (or is GHC sufficiently smart to optimize it away)?
You might be interested in Lightweight Monadic Regions http://okmij.org/ftp/Haskell/regions.html#light-weight which solve the problem (IMHO) in a much cleaner way, i.e. w/o explicit closing and also w/o using finalizers. Cheers Ben

* Ben Franksen:
You might be interested in Lightweight Monadic Regions
http://okmij.org/ftp/Haskell/regions.html#light-weight
which solve the problem (IMHO) in a much cleaner way, i.e. w/o explicit closing and also w/o using finalizers.
Is this approach composeable in the sense that you can combine code written in this code with code from another library? I don't think so. The other library might provide something like IORef, and then it's impossible to uphold static guarantees. IMHO, this rules out such an approach (until it's part of the standard library and forced upon everyone, which seems unlikely).

Florian Weimer wrote:
* Ben Franksen:
You might be interested in Lightweight Monadic Regions
http://okmij.org/ftp/Haskell/regions.html#light-weight
which solve the problem (IMHO) in a much cleaner way, i.e. w/o explicit closing and also w/o using finalizers.
Is this approach composeable in the sense that you can combine code written in this code with code from another library? I don't think so.
I see no reason why not.
The other library might provide something like IORef, and then it's impossible to uphold static guarantees.
The way it is implemented for instance in the regions package, you can lift IO actions into the Region monad, as there are instance MonadCatchIO pr => MonadCatchIO (RegionT s pr) instance MonadIO pr => MonadIO (RegionT s pr) Or maybe I don't understand your objection?
IMHO, this rules out such an approach (until it's part of the standard library and forced upon everyone, which seems unlikely).
I don't think it is necessary or even desirable to enforce this, or any other style of programming, especially not by standard library design. Cheers Ben

* Ben Franksen:
The other library might provide something like IORef, and then it's impossible to uphold static guarantees.
The way it is implemented for instance in the regions package, you can lift IO actions into the Region monad, as there are
instance MonadCatchIO pr => MonadCatchIO (RegionT s pr) instance MonadIO pr => MonadIO (RegionT s pr)
Or maybe I don't understand your objection?
The other library would need to be lowered to the IO monad, which seems to put undue constraints on resource lifetimes.
IMHO, this rules out such an approach (until it's part of the standard library and forced upon everyone, which seems unlikely).
I don't think it is necessary or even desirable to enforce this, or any other style of programming, especially not by standard library design.
So what are the other options, besides manually writing something based on some IORef Maybe ForeignPtr a? In my opinion, the handle-based style is more general than the regions-based style. Resources in a cache lack a proper region-based life-time, for instance. It is possible to go back from region-based resource management to handles, but you need to spawn a thread for each resource, just as in Erlang: module Main where import Prelude (putStrLn) import Handles main = do h <- newHandle openHandle h "/etc/passwd" line1 <- getLine h line2 <- getLine h closeHandle h putStrLn line1 putStrLn line2 module Handles (Handle, newHandle, openHandle, closeHandle, getLine) where import Prelude (IO, String, error, ($), return, show) import Data.Maybe import Control.Concurrent (forkIO) import Control.Concurrent.MVar import Control.Exception (IOException) import System.Path (asAbsPath) import Control.Monad.IO.Class (liftIO) import Control.Monad.CatchIO (catch) import System.IO.SaferFileHandles hiding (getLine) data Request = Open String | Close | GetLine data Result = Success | Failure String | Line String data Handle = MkHandle { request :: MVar Request, result :: MVar Result } newHandle :: IO Handle newHandle = do req <- newEmptyMVar res <- newEmptyMVar let h = MkHandle {request = req, result = res} in do forkIO $ worker h return h forcePut :: MVar a -> a -> IO () forcePut mvar v = do okay <- tryPutMVar mvar v if okay then return () else error "invalid state" -- Erlang-style worker process which encapsulates the state. worker :: Handle -> IO () worker MkHandle {request = request, result = result} = runRegionT $ do req <- liftIO $ takeMVar request case req of Open path -> do -- FIXME: error handling handle <-openFile (asAbsPath path) ReadMode liftIO $ forcePut result Success run handle Close -> return () _ -> liftIO $ forcePut result $ Failure "handle not open" where run handle = do req <- liftIO $ takeMVar request case req of Open _ -> do liftIO $ forcePut result $ Failure $ "handle already open" Close -> return () GetLine -> do s <- hGetLine handle liftIO $ forcePut result $ Line s run handle openHandle :: Handle -> String -> IO () openHandle MkHandle {request = request, result = result} path = do forcePut request (Open path) res <- takeMVar result case res of Success -> return () Failure s -> error s closeHandle :: Handle -> IO () closeHandle MkHandle {request = request} = forcePut request Close getLine :: Handle -> IO String getLine MkHandle {request = request, result = result} = do forcePut request GetLine res <- takeMVar result case res of Line s -> return s Failure s -> error s
participants (6)
-
Antoine Latter
-
Ben Franksen
-
Florian Weimer
-
Henning Thielemann
-
Jason Dagit
-
Michael Snoyman