
* 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