[Haskell-cafe] using ResourceT with MVars

Michael Snoyman michael at snoyman.com
Wed May 2 11:06:48 CEST 2012


On Wed, May 2, 2012 at 11:36 AM, Warren Harris <warrensomebody at gmail.com> wrote:
> I would like to use LevelDB in my code, and the HEAD version of
> leveldb-haskell now uses runResourceT to manage open db connections and
> iterators. I would also like to run multiple threads, and coordinate them
> for transaction-like behavior, i.e. read and writing data without
> interruption. LevelDB doesn't support transactions itself, so the
> alternative would seem to be using MVars for mutual exclusion.
>
> With the 0.0.3 version of leveldb-haskell, the get and put operations were
> in the IO monad, which made it trivial to write something like this:
>
> withMVar state $ \db -> do
>   maybeValue <- get db rdOpts key
>   put db wrOpts key $ maybe init incr maybeValue
>
> Now with the HEAD version, the get and put operations have types:
>
> get :: MonadResource m => DB -> ReadOptions -> ByteString -> m
> (Maybe ByteString)
> put :: MonadResource m => DB -> WriteOptions -> ByteString -> ByteString ->
> m ()
>
> I don't think it makes sense in general to lift the withMVar into
> MonadResource and use runResourceT to run its body in IO. This would not
> satisfy the intention behind using ResourceT -- resource allocated inside
> the withMVar body would be deallocated when the withMVar scope is exited,
> rather than being managed by the outermost ResourceT. (Although, in this
> case we aren't allocating any resources, so maybe it's a moot point for my
> simple example.)
>
> I also don't think it makes sense to use takeMVar and putMVar instead of
> withMVars as this would subvert the exception handling that withMVars
> provides. And my attempts to define a withMVarR (in the ResourceT IO monad)
> also seem to require runResourceT:
>
> withMVarR :: MVar a -> (a -> ResourceT IO b) -> ResourceT IO b
> withMVarR m io = do
>   -- mask $ \restore -> do
>     a <- lift $ takeMVar m
>     b <- {-restore-} (io a) `onExceptionR` (lift $ putMVar m a)
>     lift $ putMVar m a
>     return b
>
> onExceptionR :: ResourceT IO a -> ResourceT IO b -> ResourceT IO a
> onExceptionR a b = do
>   runResourceT $ transResourceT (\a -> transResourceT (onException a) b) a
>
> Maybe I need to create a "HasMVar" class analogous to HasRef?
> (http://hackage.haskell.org/packages/archive/conduit/0.0.0/doc/html/Control-Monad-Trans-Resource.html#t:HasRef)
>
> I'd appreciate any suggestions on how to make these fit together.
>
> Warren
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

I don't really know the details of LevelDB, but if the question is
"how do I run MVar operations in ResourceT", the answer would be
lifted-base[1]. Since ResourceT is an instance of MonadBaseControl,
you can use any of the functions in Control.Concurrent.MVar.Lifted.

Michael

[1] http://hackage.haskell.org/packages/archive/lifted-base/0.1.1/doc/html/Control-Concurrent-MVar-Lifted.html



More information about the Haskell-Cafe mailing list