Monads as control structures?

Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops using monads to keep track of state? I know there's things like "until", but honestly that's not quite what I'm looking for. I just think there should be a simple way to say "execute this block of code 10 times" without having to wrap it up in recursion. Haskell seems to me to be a very powerful language, and it looks like it should be possible to define control structures such as for loops using monads.

Creighton Hogg wrote:
Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops using monads to keep track of state?
I know there's things like "until", but honestly that's not quite what I'm looking for.
I just think there should be a simple way to say "execute this block of code 10 times" without having to wrap it up in recursion.
Haskell seems to me to be a very powerful language, and it looks like it should be possible to define control structures such as for loops using monads.
Could Control.Monad.replicateM or Control.Monad.replicateM_ be what you are looking for? /Björn

Try this: This line is before the loop sequence_ $ replicate 10 $ do line 1 line 2 ... last line This line is after the loop Now you can use shorthand via loopN n block = sequence_ $ replicate n block So that you can write: This line is before the loop loopN 10 $ do line 1 line 2 ... last line This line is after the loop If you need a loop parameter "mapM/mapM_ block [1...10]" works well. Creighton Hogg wrote:
Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops using monads to keep track of state?
I know there's things like "until", but honestly that's not quite what I'm looking for.
I just think there should be a simple way to say "execute this block of code 10 times" without having to wrap it up in recursion.
Haskell seems to me to be a very powerful language, and it looks like it should be possible to define control structures such as for loops using monads. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Oct 27, 2005, at 11:54 AM, Creighton Hogg wrote:
Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops using monads to keep track of state?
I know there's things like "until", but honestly that's not quite what I'm looking for.
I just think there should be a simple way to say "execute this block of code 10 times" without having to wrap it up in recursion.
Haskell seems to me to be a very powerful language, and it looks like it should be possible to define control structures such as for loops using monads.
One way is to create a list of the actions you want to execute, and then use one of the sequence family of functions. The actions can share state with an IORef or STRef or whatever. Another option is to use a fold with >>= to allow actions to pass their results directly to the next action. This works even in "stateless" monads like the list monad. Some examples using sequence: forMonad :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m () forMonad init cond inc f = sequence_ $ map f $ takeWhile cond $ iterate inc init xTimes :: Monad m => Int -> (Int -> m ()) -> m () xTimes x f = sequence_ $ map f [0..(x-1)] main = do { forMonad 0 (<10) (+1) (putStrLn . show); xTimes 10 (\_ -> putStrLn "hi") }

Creighton Hogg wrote:
Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops using monads to keep track of state?
http://www.xoltar.org/2003/sep/09/haskellLoops.html Hope that helps, Bryn

Hello Creighton, Thursday, October 27, 2005, 7:54:22 PM, you wrote: CH> Haskell seems to me to be a very powerful language, and it CH> looks like it should be possible to define control CH> structures such as for loops using monads. it's my own lib: -- |Conditional execution whenM cond action = do allow <- cond when allow action -- |Execute `action` only on (Just ...) value, returned by `x` whenJustM x action = x >>= maybe (return Nothing) action -- |Repeat forever repeat_foreverM action = do action repeat_foreverM action -- |Control structure like to `while` in Pascal repeat_whileM inp cond out = do x <- inp if (cond x) then do out x repeat_whileM inp cond out else return x -- |Control structure like to `repeat-until` in Pascal repeat_untilM action = do done <- action when (not done) $ do repeat_untilM action -- |Execute `action` on `x`, then on each element of list, returned by `action` and further recursively recursiveM action x = action x >>= mapM_ (recursiveM action) -- |Execute `action` recursively if `cond` is true and only on `x` otherwise recursiveIfM cond action x = if cond then recursiveM action x else (action x >> return ()) i also like to use mapM to iterate over lists: xs_processed <- (`mapM` xs) $ \x -> do -- some code using `x` return ... -- Best regards, Bulat mailto:bulatz@HotPOP.com
participants (6)
-
Björn Bringert
-
Bryn Keller
-
Bulat Ziganshin
-
ChrisK
-
Creighton Hogg
-
Robert Dockins