[Haskell-cafe] Bracket around every IO computation monad
Mitar
mmitar at gmail.com
Sun Nov 7 19:40:39 EST 2010
Hi!
I have a class Neuron which has (among others) two functions: attach
and deattach. I would like to make a way to call a list/stack/bunch of
attach functions in a way that if any of those fail (by exception),
deattach for previously already attached values (called attach on
them) are deattached (called deattach on them).
I have come up with such way:
data Growable where
Growable :: Neuron n => LiveNeuron n -> Growable
growNeurons :: [IO Growable] -> IO [Growable]
growNeurons attaches = growNeurons' attaches []
where growNeurons' [] ls = return ls
growNeurons' (a:ats) ls = bracketOnError a (\(Growable l) ->
deattach l) (\l -> growNeurons' ats (l:ls))
So I give growNeurons a list of attach actions and it returns a list
of attached values ((live)neurons). This works nice, but syntax to use
it is ugly:
neurons <- growNeurons [
do { a <- attach nerve1; return $ Growable a },
do { a <- attach nerve2; return $ Growable a },
do { a <- attach nerve3; return $ Growable a }
]
Types of attach and deattach are (if I simplify):
attach :: Nerve n -> IO (LiveNeuron n)
deattach :: LiveNeuron n -> IO ()
Growable is only used so that I can put actions of different type in the list.
It seems to me that all this could be wrapped into a monad. So that I
would be able to call something like:
neurons <- growNeurons' $ do
attach nerve1
attach nerve2
attach nerve3
Where I would be allowed to call actions of a special type class which
defined also clean-up function (in my case called deattach). And which
would be called if there was any exception thrown (and then at the end
rethrown). Otherwise, the result would be a list of all computed
values. In my case all this in IO monad.
So it is possible that evaluation of monad actions would be stacked
inside of bracketOnError and in a case of error clean-up functions
would be called, otherwise returns a list of results?
Mitar
More information about the Haskell-Cafe
mailing list