bracketOnError, while, forever

Hi, I just found the rather useful function 'bracketOnError' in Network.hs and was wondering why it is not exported. You need this combinator every time you fork off a computation with an acquired resource, which happens pretty often in network code, so I think making it available would be worthwhile. On a similar note, I find myself using two rather simple combinators frequently but have no place where to put them: while :: (Monad m) => m Bool -> m a -> m () while cond f = cond >>= flip when (f >> while cond f) forever :: (Monad m) => m a -> m () forever f = while (return True) f 'while', at least, would a nice addition to Control.Monad, IMHO. Peter

Peter Simons
while :: (Monad m) => m Bool -> m a -> m () while cond f = cond >>= flip when (f >> while cond f)
forever :: (Monad m) => m a -> m () forever f = while (return True) f
forever performs unnecessary computation which can't be optimized out by the compiler before specializing the monad (because the compiler can't use monad laws). Why not forever f = f >> forever f or forever f = loop where loop = f >> loop ? I don't know which is better - I guess the second gives better space behavior with some monads if it's not inlined (avoids recomputation of identical copies), but maybe the first actually allows GHC to optimize the case of IO better by not materializing a closure. I don't like the point-free style of the first either. while cond f = do c <- cond when c (f >> while cond f) -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

Peter Simons
On a similar note, I find myself using two rather simple combinators frequently but have no place where to put them:
while :: (Monad m) => m Bool -> m a -> m () while cond f = cond >>= flip when (f >> while cond f)
forever :: (Monad m) => m a -> m () forever f = while (return True) f
'while', at least, would a nice addition to Control.Monad,
I agree that these sorts of combinators are frequently useful. However, there is a reasonable variety in the possible signatures one might assign to the control-flow notion of "while". For instance, how about while :: Monad m => Bool -> m Bool -> m () while True f = f >>= \b-> while b f while False f = return () There are other control-flow analogies like until :: Monad m => m Bool -> m () until f = f >>= \b-> if b then return () else until f for :: Monad m => Int -> m a -> m () for 0 f = return () for (n+1) f = f >> for n f which probably also have a few possible monadic variations. Regards, Malcolm

On Mon, Feb 07, 2005 at 01:37:53PM +0000, Malcolm Wallace wrote:
I agree that these sorts of combinators are frequently useful. However, there is a reasonable variety in the possible signatures one might assign to the control-flow notion of "while". For instance, how about
while :: Monad m => Bool -> m Bool -> m () while True f = f >>= \b-> while b f while False f = return ()
There are other control-flow analogies like
until :: Monad m => m Bool -> m () until f = f >>= \b-> if b then return () else until f
for :: Monad m => Int -> m a -> m () for 0 f = return () for (n+1) f = f >> for n f
which probably also have a few possible monadic variations.
Regards, Malcolm
I often define the following, and usually just define them as IO as I haven't found a non-IO use for them yet (okay, ST and the recent STM): -- clashes with your for for :: [a] -> (a -> IO b) -> IO () for = flip mapM_ loop :: IO a -> IO () loop = sequence_ . repeat I have no idea whether GHC is smart enough to optimize the lists away (in loop and in e.g. "for [1..100] ..."), though it hasn't caused me problems in practice. I'm rather fond of lists of IO-actions, which is probably why I once wrote the following OpenGL code: renderPrimitive Polygon $ do sequence_ $ concat $ transpose [colors, vertices] where both `colors' and `vertices' are lists of actions which respectively change the current OpenGL color and draw a vertex. Greetings, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

In article <878y60v8hk.fsf@peti.cryp.to>, Peter Simons
while :: (Monad m) => m Bool -> m a -> m () while cond f = cond >>= flip when (f >> while cond f)
I use this: while :: (Monad m) => m (Maybe a) -> m [a]; while mma = do { ma <- mma; case ma of { Just a -> do { as <- while mma; return (a:as); }; _ -> return []; }; }; It is not tail-recursive however. I have a different function if I don't need results: whileDo :: (Monad m) => m Bool -> m (); whileDo mb = mb >>= \b -> if b then whileDo mb else return (); I also have a highly generalised "for" function, but it uses my own Functor classes: for :: (ExtractableFunctor f,FunctorApplyReturn m) => (a -> m b) -> (f a -> m (f b)); for foo fa = fextract (fmap foo fa); In my libraries, [] is an instance of ExtractableFunctor, and Monad is a subclass of FunctorApplyReturn (which has return and liftM2). -- Ashley Yakeley, Seattle WA

Hi, speaking of additions to the libraries, i'd like to mention a few functions from http://haskell.org/hawiki/LicensedPreludeExts that I think deserve to be in the libs. First of all | -- Cale Gibbard | comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering | comparing p x y = compare (p x) (p y) fits nicely with the ...By functions from Data.List. Since there's no easy way to catch failure of read operations, | readM :: (Monad m, Read a) => String -> m a | readM s = case [x | (x,t) <- reads s, ("","") <- lex t] of | [x] -> return x | [] -> fail "Prelude.readM: no parse" | _ -> fail "Prelude.readM: ambiguous parse" this function seems to be quite natural. Finally, | -- Koen Claessen | selections :: [a] -> [(a,[a])] | selections [] = [] | selections (x:xs) = (x,xs) : [ (y,x:ys) | (y,ys) <- selections xs ] | | permutations :: [a] -> [[a]] | permutations [] = [[]] | permutations xs = | [ y : zs | | (y,ys) <- selections xs | , zs <- permutations ys | ] are quite useful (maybe they should be named select and permute since most Data.List names seem to be imperatives).
forever :: (Monad m) => m a -> m () forever f = while (return True) f a more logical name would be repeatM_
Btw, is there some rule which prelude functions should have monadic equivalents in Control.Monad? There is mapM, filterM, zipWithM, foldM and replicateM, but no foldrM, unfoldM, repeatM, allM, anyM (the last three are easily defined using sequence, but so are mapM and replicateM). What do you think? Thomas
participants (6)
-
Ashley Yakeley
-
Malcolm Wallace
-
Marcin 'Qrczak' Kowalczyk
-
Peter Simons
-
Remi Turk
-
Thomas Jäger