Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-03-02 Thread Roel van Dijk
Looks good! A few tips:

  funcList :: [Int - Int]
  funcList = [\_ - 1, \_ - 2, \_ - 3]
funcList = [const 1, const 2, const 3]


  iterateCircularFL :: [a - b] - (a - b, [a - b])
  iterateCircularFL (x:xs) = (x, concat [xs, [x]])
{- If you use cycle in main then you do not need this function at all. -}

  applyCircularFL :: a - [a - b] - (b, [a - b])
  applyCircularFL arg fList =
   let
 (currentFunc, iteratedList) = iterateCircularFL fList
   in (currentFunc arg, iteratedList)
{- If the list of functions is infinite then we do not have to worry
about exhausting it, although an empty list will still cause a pattern
match failure. -}
applyCircularFL :: a - [a - b] - (b, [a - b])
applyCircularFL arg (f:fs) = (f arg, fs)

testTraversal i l
 |  i == 0 = putStr Done.
 |  i  0 = do {
   putStr Execution ;
   putStr (show i);
   putStr  returned ;
   putStr (show val);
   putStr .\n;
   testTraversal (i - 1) newList
}
  where (val, newList) = applyCircularFL i l

{- Transform funcList into an infinite list to simplify things -}
main = testTraversal 5 $ cycle funcList

I hope these tips are usefull :-)

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


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-03-01 Thread Aaron Altman
A big thanks to you all for the discussion.  I have determined that a 
monad is actually not the best representation of a circular list of 
functions.  I was able to implement it without any special syntax or 
unusual typing.  For the curious:


--

funcList :: [Int - Int]
funcList = [\_ - 1, \_ - 2, \_ - 3]

iterateCircularFL :: [a - b] - (a - b, [a - b])
iterateCircularFL (x:xs) = (x, concat [xs, [x]])

applyCircularFL :: a - [a - b] - (b, [a - b])
applyCircularFL arg fList =
 let
   (currentFunc, iteratedList) = iterateCircularFL fList
 in (currentFunc arg, iteratedList)

testTraversal i l
 |  i == 0 = putStr Done.
 |  i  0 = do {
   putStr Execution ;
   putStr (show i);
   putStr  returned ;
   putStr (show val);
   putStr .\n;
   testTraversal (i - 1) newList
}
  where (val, newList) = applyCircularFL i l

main = do
 testTraversal 5 funcList
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-02-28 Thread Bas van Dijk
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


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-02-28 Thread Felipe Lessa
On Thu, Feb 28, 2008 at 4:28 AM, Aaron Altman [EMAIL PROTECTED] wrote:
  runActionAndIterate :: [a - a] - a - (a, [a - a])
  runActionAndIterate (currentAction:actionList) actionInput =
  (currentAction actionInput, concat [actionList, [currentAction]])

  shiftActionList :: [a - a] - [a - a]
  shiftActionList (currentHead:rest) = concat [rest, [currentHead]]

As a side note, it's not good to recreate the list (using 'concat')
for every item as it is an O(n) operation. Bas van Dijk's 'always'
(also called 'forever'[1]) is an option, but you can also create a
circular list using the simple function 'cycle'[2] and your functions
above would become

runActionAndIterate (currentAction:actionList) actionInput =
  (currentAction actionInput, actionList)

shiftActionList = tail

[1] 
http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#v%3Aforever
[2] 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Acycle

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


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-02-28 Thread Felipe Lessa
On Thu, Feb 28, 2008 at 8:15 AM, Roel van Dijk [EMAIL PROTECTED] wrote:
 I'm nitpicking but,

Not a nitpick, a great difference =). As someone else already said on
this list, it's not good to answer e-mails in the early morning heh.

Thanks,

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


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-02-28 Thread Roel van Dijk
I'm nitpicking but,

On Thu, Feb 28, 2008 at 11:44 AM, Felipe Lessa [EMAIL PROTECTED] wrote:
 Bas van Dijk's 'always' (also called 'forever'[1])

forever a  = a  forever a
always f z = f z = always f

Forever doesn't pass the result of the action to its recursive call,
always does.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-02-28 Thread Felipe Lessa
On Thu, Feb 28, 2008 at 7:44 AM, Felipe Lessa [EMAIL PROTECTED] wrote:
  Bas van Dijk's 'always' (also called 'forever'[1])

Sorry, of course

always' :: Monad m = (a - m a) - (a - m ())
forever :: Monad m = (m a) - (m ())

are of different types and so are different functions.

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


Re: [Haskell-cafe] Wrong kind when attempting to build a monad for a circular list of functions

2008-02-27 Thread Luke Palmer
On Thu, Feb 28, 2008 at 7:28 AM, Aaron Altman [EMAIL PROTECTED] wrote:
  newtype CircularFuncList funcList arg = CircularFuncList (funcList -
  arg - (arg, funcList))

  instance Monad (CircularFuncList funcList arg) where
   return a = CircularFuncList (\funcList a - (a, funcList))
   CircularFuncList currentFuncList currentArg = argTransform =
 let result = argTransform $ (head currentFuncList) currentArg
 newFuncList = map argTransform $ shiftActionList currentFuncList
 in CircularFuncList newFuncList result

So some standard monads are:

  instance Monad [] where ...
  instance Monad Maybe where ...

Note how they are all missing a type argument, i.e. not:

  instance Monad (Maybe Int) where ...

So your monad needs to be, say:

  instance Monad (CircularFuncList funcList) where ...

But see below...

  -

  I get an error that CircularFuncList funcList arg has kind * while Monad
  is looking for * - *.  This is a first attempt so it may be I'm a ways
  off from a monad that implements a circular list of functions.  That is
  the goal though.  What advice can you offer?

I'm not sure how CircularFuncList is a monad.  In fact it doesn't even
look like a Functor (because arg appears both as an argument and a
return in your data type definition).  How do you intend your monad to
be used?  That is, when a user writes:

foo :: CircularFuncList func a
foo = do
x - ...
y - ... x
...

What are the primitive operations (the ...s here) and what does it
mean to sequence them like this?  Describing this in words might help
you implement this, or more likely, help you realize that a monad
isn't what you thought it is :-)

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