[Haskell-cafe] Re: Iteratee-based IO and lightweight monadic
regions in the wild
Ben Franksen
ben.franksen at online.de
Sat Feb 14 19:51:24 EST 2009
Artyom Shalkhakov wrote:
> Is anybody planning to use these shiny new ways for doing IO?
Interesting that you ask. I am currently using the 'lightweight monadic
region' approach to manage network resources (so called 'channels',
connections to a named variable; the context is Haskell support for a
certain network protocol used in some distributed control systems). These
channels should be freed in a timely fashion and must not be used after
freeing them, just like file handles. A complication arises due to channels
being subordinate to another type of resource, so called 'client contexts',
which must be handled in a similar fashion. Another complication is due to
the underlying C library's heavy use of callbacks to signal changes related
to a channel (such as value change or connection loss). Remembering a
message by Jules Bean some time ago on this list
(http://www.haskell.org/pipermail/haskell-cafe/2007-July/028501.html) I
tried to integrate his ideas of "threading one monad through another" with
monadic regions, which was a very interesting and enlightening experience.
Somewhere along the way I replaced his MPTC with associated type synonyms,
which greatly simplified the type signatures. Then I saw that RMonadIO is
indeed subsumed by InterleavableIO:
class Monad m => InterleavableIO m where
type Internals m
embed :: (Internals m -> IO a) -> m a
callback :: m a -> Internals m -> IO a
instance InterleavableIO m => RMonadIO m where
brace before after during =
embed $ \x -> bracket (before' x) (\a -> after' a x) (\a -> during' a
x)
where
before' x = callback before x
after' a x = callback (after a) x
during' a x = callback (during a) x
snag action handler = embed $ \x -> catch (action' x) (\e -> handler' e x)
where
action' x = callback action x
handler' e x = callback (handler e) x
lIO = embed . const
which is indeed exactly the same implementation for the instances as in the
original regions paper (and source), only that in my case the exceptions
don't have to be 'cleansed' of handles (which could otherwise leak from a
region).
I am currently working on integrating concurrency into my monadic regions.
Specifically, I want to be able to re-assign certain resources, like
with 'shDup' but not to a parent region but to a completely new,
independent region that shares the same 'client context' but runs in
another thread. This is very much in flux, however, and I still have to
check it is actually safe.
Cheers
Ben
More information about the Haskell-Cafe
mailing list