[Haskell-cafe] Monads as control structures?

Bulat Ziganshin bulatz at HotPOP.com
Thu Oct 27 16:15:37 EDT 2005


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 at HotPOP.com





More information about the Haskell-Cafe mailing list