Bracket around every IO computation monad

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

(I won't answer your main question, I'll just write some notes on your
current code.)
On Sun, Nov 7, 2010 at 10:40 PM, Mitar
neurons <- growNeurons [ do { a <- attach nerve1; return $ Growable a }, do { a <- attach nerve2; return $ Growable a }, do { a <- attach nerve3; return $ Growable a } ]
Note that this is the same as neuros <- growNeurons [ Growable <$> attach nerve1, Growable <$> attach nerve2, Growable <$> attach nerve3]
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.
Well, you could use attachG :: Nerve n -> IO Growable attachG n = Growable <$> attach n ... neurons <- growNeurons [attachG nerve1, attachG nerve2, attachG nerve3] Cheers, -- Felipe.

Hi!
On Mon, Nov 8, 2010 at 1:50 AM, Felipe Almeida Lessa
(I won't answer your main question, I'll just write some notes on your current code.)
Thanks. This also helped. But is it possible to define a Monad like I described? So that all actions would be wrapped in a bracket, which would be stacked? Mitar

Well, I guess you could try something like:
{-# LANGUAGE GADTs #-}
import Control.Exception (bracketOnError) import Control.Monad ((>=>))
-- from package 'operational' import Control.Monad.Operational
data BracketedOperation a where Bracketed :: IO a -> (a -> IO b) -> BracketedOperation a
type BracketedProgram a = ProgramT BracketedOperation IO a
interpret :: BracketedProgram a -> IO a interpret = viewT >=> eval where eval :: ProgramViewT BracketedOperation IO a -> IO a eval (Return a) = return a eval (Bracketed acquire release :>>= is) = bracketOnError acquire release $ interpret . is
Now you could have: ] attachN :: Nerve n -> BracketedProgram (LiveNeuron n) ] attachN n = singleton (Bracketed (attach n) dettach) And your code would become: ] neurons <- interpret $ do ] attachN nerve1 ] attachN nerve2 ] attachN nerve3 Note that I haven't tested this code, but it compiles :). Cheers! -- Felipe.

Hi! Felipe and Bas, thank you for your suggestions. They really opened two new worlds to me. ;-) I didn't know about those libraries. I was hopping of succeeding making a "bracketing" monad by hand, to learn something and to make my first monad. But was not successful. I hope those approaches with libraries will be a good guide to me. Mitar

On Mon, Nov 15, 2010 at 9:44 PM, Mitar
I was hopping of succeeding making a "bracketing" monad by hand, to learn something and to make my first monad. But was not successful. I hope those approaches with libraries will be a good guide to me.
My approach using 'operational' package is equivalent to creating your own monad. The beauty of 'operational' is that you don't need to worry about the pumbling of the monad, you just need to specify what to do with your operations. That said, I don't know what 'regions' may do for you that the simple monad I presented doesn't. Bas, what are the advantages? As one disadvantage, I'd say that using regions sound more complicated than just using 'operational' =). Cheers! =D -- Felipe.

Hi!
My approach using 'operational' package is equivalent to creating your own monad. The beauty of 'operational' is that you don't need to worry about the pumbling of the monad, you just need to specify what to do with your operations.
True. Approach with "operational" is really beautiful. And it is really great when you want things done. But for me, Haskell novice who wants to learn more, it hides too much. So it is probably something I would use in my code, but on the other hand I would like an exercise of doing things by hand. So first 100 monads by hand and then such libraries are useful, but also you exactly understand what are they doing - what are they automating, which process you have been doing by hand before. So thank you for your approach. I didn't know that this can be automated in so elegant way. Mitar

On Mon, Nov 15, 2010 at 10:15 PM, Mitar
True. Approach with "operational" is really beautiful. And it is really great when you want things done. But for me, Haskell novice who wants to learn more, it hides too much. So it is probably something I would use in my code, but on the other hand I would like an exercise of doing things by hand. So first 100 monads by hand and then such libraries are useful, but also you exactly understand what are they doing - what are they automating, which process you have been doing by hand before.
That's true, doing it yourself manually helps to see that there's no magic under the hood =). After implementing the monad, I would suggest trying to prove that the monad laws hold [1]. Sometimes you think you have a monad but you don't [2]. [1] http://www.haskell.org/haskellwiki/Monad_Laws [2] http://blog.sigfpe.com/2006/11/why-isnt-listt-monad.html Cheers! -- Felipe.

On Nov 15, 2010, at 4:15 PM, Mitar wrote:
True. Approach with "operational" is really beautiful. And it is really great when you want things done. But for me, Haskell novice who wants to learn more, it hides too much. So it is probably something I would use in my code, but on the other hand I would like an exercise of doing things by hand.
Check out: http://apfelmus.nfshost.com/articles/operational-monad.html It's the paper that inspired the "operational" module.

Hi!
On Tue, Nov 16, 2010 at 1:40 AM, Alexander Solla
Check out: http://apfelmus.nfshost.com/articles/operational-monad.html It's the paper that inspired the "operational" module.
I read that yesterday. A nice read. Now I have to think how to make my own monad based on all this knowledge. (As an exercise.) Mitar

On Tue, Nov 16, 2010 at 12:50 AM, Felipe Almeida Lessa
That said, I don't know what 'regions' may do for you that the simple monad I presented doesn't. Bas, what are the advantages?
My suggestion to use regions is based on an assumption which I'm not sure is right. Mitar can answer that... The assumption being that Mitar's Nerves are scarce resources (like files for example). Meaning: 1) They have an 'open' operation yielding a 'handle' to the 'resource': attach :: Nerve n -> IO (LiveNeuron n) Compare this with: openFile :: FilePath -> IOMode -> IO Handle 2) There are one or more operations defined on these handles: someOperation :: LiveNeuron n -> IO () (I'm not sure Mitar actually has this...) Compare this with: hFileSize :: Handle -> IO Integer 3) They have a 'close' operation: deattach :: LiveNeuron n -> IO () Compare with: hClose :: Handle -> IO () 4) It's important not to leave handles open (or in this case leave nerves attached) when they don't need to be. In the case of files when you leave a file open when you're not using it anymore, other processes may not be able to use the file. (I'm not sure this is a requirement for Nerves...) 5) It's an error to apply the operations to closed handles. In the case of files, the following program is an error for example: main = do h <- openFile "foo.txt" ReadMode hClose h hFileSize h -- error: h is already closed! (Again, I'm not sure a similar requirement exists for LiveNeurons) When these five requirements apply, you may find the regions package useful. When you write a correct 'regional' layer around your scarce resources like I showed earlier, regions will provide the following guarantees: * Resources are opened in a 'region'. When the region terminates (whether normally or by raising an exception) all opened resources will be closed automatically (this was Mitar's original requirement) * It's a type-error to reference closed resources. This ensures no operations can be applied to closed resources (deattached neurons). Besides these guarantees the regions package is very expressive. It allows you to nest regions inside each other and it allows you to 'duplicate' handles to ancestor regions. This allows you to use a resource, which was opened in a nested region, in the parent of that region, as in: example :: IO () example = runRegionT $ do sn' <- runRegionT $ do sn <- saveAttach Nerve -- We can't 'return sn' because the neuron will be deattached -- when the regions terminates. -- Instead we have to 'duplicate' it which ensures it stays -- attached in the current region and will only be deattached -- in the parent region: sn' <- dup sn return sn' -- Back in the parent region we can safely apply some operation -- to the duplicated neuron: someSaveOperation sn' To read more about regions, see both the API docs of regions: http://hackage.haskell.org/package/regions and some packages that define 'regional' layers over existing scarce resources like: * http://hackage.haskell.org/package/safer-file-handles * http://hackage.haskell.org/package/regional-pointers * http://hackage.haskell.org/package/usb-safe Finally, I can also recommend Oleg's and Chung-chieh's paper about "Lightweight monadic regions": http://okmij.org/ftp/Haskell/regions.html#light-weight Regards, Bas P.S. Please apply /s/save/safe to my previously posted code. It's late...

Hi!
On Tue, Nov 16, 2010 at 2:05 AM, Bas van Dijk
The assumption being that Mitar's Nerves are scarce resources (like files for example). Meaning:
Yes. My nerves are really a scarce resource. ;-) And I haven't yet heard anybody comparing them to files. I heard that they are short and sometimes people step on some of them. But not that they are like files. ;-) I have to tell this to my fellow neuroscientists. This is a whole new paradigm. ;-) But yes, Nerves were modeled by looking at file handles. And were also made so that they fit nicely into the "bracket" function. They are mostly a wrapper around scarce resource (like display, complex computation (CPU), sensors and similar). This is why there has to be some preparation and cleanup. In fact your approach opens a whole new idea for me. Because currently my whole main program was: attach everything together, if error while attaching cleanup and exit wait until everything lives/works or until an error cleanup everything and wait until everything is really cleaned up exit The whole main program just prepares my generic data-flow computation framework I am developing. So that attaching is how all flows (called Nerves) are interconnected and then you let it live and process. So your approach is interesting because I could do cleanup at one place, and it wouldn't matter if I am doing this in the "attach" phase (which this thread is about) or any other phase.
someOperation :: LiveNeuron n -> IO ()
(I'm not sure Mitar actually has this...)
No. In fact Neurons are defined with an operation they do. You just feed them with data and they output data. In main program you do not do operations over them. You just grow/prepare them and attache/interconnect them.
4) It's important not to leave handles open (or in this case leave nerves attached) when they don't need to be. In the case of files when you leave a file open when you're not using it anymore, other processes may not be able to use the file.
(I'm not sure this is a requirement for Nerves...)
It is. Because they encapsulate also complex resources like sensors, cameras, displays, keyboard and similar things. (But they can also be quite low-level too.)
(Again, I'm not sure a similar requirement exists for LiveNeurons)
It does. Once things are cleaned up there should be no other use of them. Mitar

On Mon, Nov 8, 2010 at 1:40 AM, Mitar
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
This can be solved by using "Lightweight Monadic Regions" as implemented in my regions package[1]. What follows is an example module that demonstrates the idea: module SaveNeurons (Nerve, SaveNeuron, saveAttach, someSaveOperation) where ---------------------------------------------------------------------- -- Imports: -- from base: import Control.Monad ( liftM ) -- from monad-peel: import Control.Exception.Peel ( block ) import Control.Monad.IO.Peel ( MonadPeelIO ) -- from transformers: import Control.Monad.IO.Class ( MonadIO(liftIO) ) -- from regions: import Control.Monad.Trans.Region ( RegionT, runRegionT , Dup(dup) , AncestorRegion ) import Control.Monad.Trans.Region.OnExit ( FinalizerHandle, onExit ) ---------------------------------------------------------------------- -- Your existing types and functions: data Nerve n = Nerve data LiveNeuron n = LiveNeuron attach :: Nerve n -> IO (LiveNeuron n) attach = undefined deattach :: LiveNeuron n -> IO () deattach = undefined -- You probably also defined some operations on LiveNeurons: someOperation :: LiveNeuron n -> IO () someOperation = undefined ---------------------------------------------------------------------- -- Save regional layer: data SaveNeuron n r = SaveNeuron (LiveNeuron n) (FinalizerHandle r) saveAttach :: MonadPeelIO pr => Nerve n -> RegionT s pr (SaveNeuron n (RegionT s pr)) saveAttach nerve = block $ do n <- liftIO $ attach nerve fh <- onExit $ deattach n return $ SaveNeuron n fh someSaveOperation :: (AncestorRegion pr cr, MonadIO cr) => SaveNeuron n pr -> cr () someSaveOperation (SaveNeuron ln _) = liftIO $ someOperation ln instance Dup (SaveNeuron n) where dup (SaveNeuron ln fh) = liftM (SaveNeuron ln) $ dup fh ---------------------------------------------------------------------- -- Example: example :: IO () example = runRegionT $ do sn1 <- saveAttach Nerve someSaveOperation sn1 -- When one of these operations fail, -- all attached nerves will be detached automatically. sn2 <- saveAttach Nerve sn3 <- saveAttach Nerve someSaveOperation sn2 someSaveOperation sn3 -- We can also nest regions. runRegionT $ do someSaveOperation sn1 sn4 <- saveAttach Nerve sn5 <- saveAttach Nerve someSaveOperation sn4 someSaveOperation sn5 -- When a regions terminates all attached nerves will -- be detached automatically. Note that is a type error -- to return a save neuron from a regions: -- 'return sn5' gives a type error for example. -- If you really wish to return a save neuron you can -- 'duplicate' it to the parent region as in: -- sn5' <- dup sn5 -- return sn5' ---------------------------------------------------------------------- Feel free to ask any questions about the above code. Regards, Bas [1] http://hackage.haskell.org/package/regions

On Sun, Nov 7, 2010 at 7:40 PM, Mitar
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).
Perhaps I'm misunderstanding how this works, but it seems like this could all be done fairly simply using standard combinators in Control.Monad.
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))
Isn't this mostly a reimplementation of mapM? Given a list of [IO Growable], you map over it to put a bracket around each one, then sequence the result (which I believe performs exactly the sort of nested monadic recursion you're doing here). I think that something like this ought to be equivalent: growNeurons :: [IO Growable] -> IO [Growable] growNeurons = mapM (\a -> bracketOnError a (\(Growable l) -> deattach l) return)
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 } ]
Along the lines of what Felipe suggested, this could possibly be simplified to something like: growNeurons $ map (fmap Growable . attach) [nerve1, nerve2, nerve3] ...except that this won't work if the nerves have different types. In many cases there's a trivial translation to get rid of existential types, and I suspect it would work here, but I'm not sure what else you might be doing with them. Existential types tend to be more trouble than they're worth, in my experience.
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
I'm not sure why you'd want to do it this way, relying on the monad to provide the sequencing. Isn't it more convenient to use a list of neurons, as above? - C.

Hi!
On Mon, Nov 15, 2010 at 9:07 PM, C. McCann
Isn't this mostly a reimplementation of mapM? Given a list of [IO Growable], you map over it to put a bracket around each one, then sequence the result
No. There is a trick. It stacks up attach and deattach. So if for third attach something fails then both deattach for second and first nerve is called. In your example this would not happen. So the idea is that in a case of an error all computations (which are of some type class which defines necessary prepare and cleanup functions) are "unwinded". In a case of success the resulting list is returned. Mitar
participants (5)
-
Alexander Solla
-
Bas van Dijk
-
C. McCann
-
Felipe Almeida Lessa
-
Mitar