On Thu, Feb 28, 2008 at 8:28 AM, Aaron Altman <[EMAIL PROTECTED]> wrote:
>  I am working on an AI agent that will perform a finite series of actions
>  before starting the sequence over again.  I figured a circular list of
>  functions that shifts as you apply them would be the way to do it...

I think a better representation of "a finite series of actions" is a
'Monad m => [m a]' because your AI agent will likely do some side
effects when it's executing. Then if you also want to thread some
state through the actions you should have a 'Monad m => [a -> m a]':
(Another idea is to use MonadState)

import Control.Monad

walk :: (Monad m) => [a -> m a] -> a -> m a
walk = foldr (>=>) return

always :: (Monad m) => (a -> m a) -> a -> m b
always f z = f z >>= always f

ai :: (Monad m) => a -> [a -> m a] -> m a
ai z f = always (walk f) z

example = ai 0 [ \x -> print x >> return x
               , \x -> if x > 10
                       then fail "the end"
                       else return (x+1)
               ]

regards,

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

Reply via email to