bracketOnError, while, forever
Remi Turk
rturk at science.uva.nl
Mon Feb 7 16:28:22 EST 2005
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.
More information about the Libraries
mailing list