Hi All,

I just wrote a function to repeatedly transform something inside a monad using the same transforming function every time. I feel it might be dodgy though:

iterateM :: (Monad m) => (a -> m a) -> m a -> m [a]
iterateM f sm = 
  sm >>= \s -> 
  iterateM f (f s) >>= \ss -> 
  return (s:ss)

The context is that I was trying to write a state machine that responded to keyboard input:

data Event = LoYes | LoNo | LoNum -- buttons on your phone
           | ReYes | ReNo | ReNum -- buttons on his phone 

data State = State { handler :: Event -> IO State } 

main =  
  hSetBuffering stdin NoBuffering >> -- so you don't have to hit return
  iterateM (\st -> getEvent >>= handler st) (return idle) 


getEvent :: IO Event
getEvent =  
  getChar >>= \c -> case c of
  'y' -> return LoYes
  'n' -> return LoNo
  '0' -> return LoNum
  'Y' -> return ReYes
  'N' -> return ReNo
  '1' -> return ReNum
  _   -> getEvent

idle, ringing, waiting, talking :: State
idle = State $ \e -> case e of
  LoYes -> return idle
  LoNo  -> return idle
  LoNum -> putStrLn "\tCalling somebody" >> 
           return waiting
  ReYes -> return idle
  ReNo  -> return idle
  ReNum -> putStrLn "\tIt's for you-hoo" >> 
           return ringing

-- other states similar

The reason I'm worried is that this is the second time I've needed such a thing and it seems odd that it's not in the prelude already. Does it leak memory? Does it have a tail recursion problem? Is the functionality I want covered by something else? I guess I could consider [a] to be b in a regular monad but then the (\st -> getEvent >>= handler st) bit would have to juggle lists which seems meaningless.

Am I missing something or does everybody else have this iterateM in their personal prelude?

TIA,
Adrian.