Readline read_history and write_history addition
Judah Jacobson
judah.jacobson at gmail.com
Tue Jan 22 20:48:08 EST 2008
On Jan 22, 2008 3:49 PM, Yitzchak Gale <gale at sefer.org> wrote:
>
> In a library, you have a function that starts up an
> external system, runs a calculation, then shuts
> down the external system. Like this:
>
> bracketSystem :: MonadIO m => m a -> m a
> bracketSystem x = do
> startUpSystem
> ret <- x
> shutDownSystem
> return ret
>
> Now you would really like to wrap that in bracket
> to make sure that "shutDownSystem" is called even
> when an IO exception is thrown. But unfortunately,
> bracket is currently not available for MonadIO,
> nor is there any way to emulate it AFIK.
> (This is a "maybe" for HaskellPrime:
> http://hackage.haskell.org/trac/haskell-prime/ticket/110)
Following is what I've been using to solve that problem. I can add it
to that HaskellPrime ticket if people think it's useful.
==============
module IO1 where
import Control.Monad.State
import Control.Monad.Error
import Control.Exception
import System.IO
class MonadIO m => MonadIO1 m where
liftIO1 :: (forall b . IO b -> IO b) -> m a -> m a
instance MonadIO1 IO where
liftIO1 = id
instance MonadIO1 m => MonadIO1 (StateT s m) where
liftIO1 f = mapStateT (liftIO1 f)
instance (Error e, MonadIO1 m) => MonadIO1 (ErrorT e m) where
liftIO1 f = mapErrorT (liftIO1 f)
-- and so on for ReaderT, ListT, etc.
block1, unblock1 :: MonadIO1 m => m a -> m a
block1 = liftIO1 block
unblock1 = liftIO1 unblock
bracket1 :: MonadIO1 m => m a -> (a -> IO b) -> (a -> m c) -> m c
bracket1 before after thing = block1 $ do
a <- before
r <- liftIO1 (handle (\e -> do {after a; throw e}))
(unblock1 (thing a))
liftIO (after a)
return r
-- example: bracket file operations in an arbitrary monad
withFile1 :: MonadIO1 m => FilePath -> IOMode -> (Handle -> m a) -> m a
withFile1 name mode = bracket1 (liftIO (openFile name mode)) hClose
==============
Note that in bracket1, the "after" action must run in IO. In
practice, that hasn't been a problem for me. In fact, since the
"after" clause might run in response to an asynchronous exception, I
don't see how it could be sequenced with an arbitrary monad, anyway.
Best wishes,
-Judah
More information about the Libraries
mailing list