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") }

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to