[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Heinrich Apfelmus
Bertram Felgenhauer wrote:
 Yves Parès wrote:

 I answered my own question by reading this monad-prompt example:
 http://paste.lisp.org/display/53766

 But one issue remains: those examples show how to make play EITHER a human
 or an AI. I don't see how to make a human player and an AI play SEQUENTIALLY
 (to a TicTacToe, for instance).
 
 A useful idea is to turn the construction upside-down - rather than
 implementing the game logic using MonadPrompt (or operational),
 implement the players in such a monad.
 
 A sketch:
 
 {-# LANGUAGE GADTs, EmptyDataDecls #-}
 import Control.Monad.Prompt hiding (Lift)
 
 data Game -- game state
 data Move -- move
 
 data Request m a where
 Board:: Request m Game
 MakeMove :: Move - Request m ()
 Lift :: m a - Request m a
 
 type Player m a = Prompt (Request m) a

Just a small simplification: it is not necessary to implement the  Lift
 constructor by hand, the  operational  library implements a generic
monad transformer. The following will do:

import Control.Monad.Operational

data Request a where
Board:: Request Game
MakeMove :: Move - Request ()

type Player m a = ProgramT Request m a

game :: Monad m = Player m () - Player m () - m ()
game p1 p2 = do
g - initGame
eval' g p1 p2
where
eval' g p1 p2 = viewT p1 = \p1' - eval g p1' p2

eval :: Monad m = Game -
   - Prompt Request m ()
   - Player m ()
   - m ()
eval g (Return _)_  = return ()
eval g (Board   := p1) p2 = eval' g (p1 g) p2
eval g (MakeMove mv := p1) p2 =
makeMove mv g = \g - eval' g p2 (p1 ())

This way, you are guaranteed not to break the lifting laws, too.

 What have we achieved? Both players still can only access functions from
 whatever monad m turns out to be. But now each strategy can pile its own
 custom monad stack on the  Player m  monad! And of course, the use of
 the m Monad is completely optional.

Of course, the custom monad stack has to provide a projection back to
the  Player m a  type

   runMyStackT :: MyStackT (Player m) a - Player m a

Fortunately, you can't expect anything better anyway! After all, if the
 game  function were to accept say  LogicT (Player m)  as well, this
would mean that the player or AI could interleave the game arbitrarily,
clearly not a good idea.

 Mapping between various 'm' monads may also be useful:
 
 mapPlayerM :: forall m1 m2 a . (forall a . m1 a - m2 a)
- Player m1 a - Player m2 a
 mapPlayerM m1m2 pl = runPromptC return handle pl where
 handle :: Request m1 x - (x - Player m2 a) - Player m2 a
 handle (Lift a)  x = prompt (Lift (m1m2 a)) = x
 handle (MakeMove mv) x = prompt (MakeMove mv) = x
 handle (Board)   x = prompt (Board) = x
 
 This could be used to lock out the AI player from using IO, say.

Shouldn't this actually be a member of the  MonadTrans  class?

mapMonad :: (Monad m1, Monad m2, MonadTrans t) =
(forall a . m1 a - m2 a) - t m1 a - t m2 a

?

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Limestraël
I have some difficulties to see the use of PromptT, because in the tutorial,
this type is never mentioned, and its operations (Return and :=) are
instead constructors of ProgramT...

Would you have some concrete examples? Because there I'm a bit lost (since
the tutorial doesn't match the operational package as it is, because of the
type PromptT)...

2010/4/14 Heinrich Apfelmus apfel...@quantentunnel.de

 Bertram Felgenhauer wrote:
  Yves Parès wrote:
 
  I answered my own question by reading this monad-prompt example:
  http://paste.lisp.org/display/53766
 
  But one issue remains: those examples show how to make play EITHER a
 human
  or an AI. I don't see how to make a human player and an AI play
 SEQUENTIALLY
  (to a TicTacToe, for instance).
 
  A useful idea is to turn the construction upside-down - rather than
  implementing the game logic using MonadPrompt (or operational),
  implement the players in such a monad.
 
  A sketch:
 
  {-# LANGUAGE GADTs, EmptyDataDecls #-}
  import Control.Monad.Prompt hiding (Lift)
 
  data Game -- game state
  data Move -- move
 
  data Request m a where
  Board:: Request m Game
  MakeMove :: Move - Request m ()
  Lift :: m a - Request m a
 
  type Player m a = Prompt (Request m) a

 Just a small simplification: it is not necessary to implement the  Lift
  constructor by hand, the  operational  library implements a generic
 monad transformer. The following will do:

import Control.Monad.Operational

data Request a where
Board:: Request Game
MakeMove :: Move - Request ()

type Player m a = ProgramT Request m a

game :: Monad m = Player m () - Player m () - m ()
 game p1 p2 = do
g - initGame
eval' g p1 p2
where
eval' g p1 p2 = viewT p1 = \p1' - eval g p1' p2

eval :: Monad m = Game -
   - Prompt Request m ()
   - Player m ()
   - m ()
eval g (Return _)_  = return ()
eval g (Board   := p1) p2 = eval' g (p1 g) p2
eval g (MakeMove mv := p1) p2 =
makeMove mv g = \g - eval' g p2 (p1 ())

 This way, you are guaranteed not to break the lifting laws, too.

  What have we achieved? Both players still can only access functions from
  whatever monad m turns out to be. But now each strategy can pile its own
  custom monad stack on the  Player m  monad! And of course, the use of
  the m Monad is completely optional.

 Of course, the custom monad stack has to provide a projection back to
 the  Player m a  type

   runMyStackT :: MyStackT (Player m) a - Player m a

 Fortunately, you can't expect anything better anyway! After all, if the
  game  function were to accept say  LogicT (Player m)  as well, this
 would mean that the player or AI could interleave the game arbitrarily,
 clearly not a good idea.

  Mapping between various 'm' monads may also be useful:
 
  mapPlayerM :: forall m1 m2 a . (forall a . m1 a - m2 a)
 - Player m1 a - Player m2 a
  mapPlayerM m1m2 pl = runPromptC return handle pl where
  handle :: Request m1 x - (x - Player m2 a) - Player m2 a
  handle (Lift a)  x = prompt (Lift (m1m2 a)) = x
  handle (MakeMove mv) x = prompt (MakeMove mv) = x
  handle (Board)   x = prompt (Board) = x
 
  This could be used to lock out the AI player from using IO, say.

 Shouldn't this actually be a member of the  MonadTrans  class?

mapMonad :: (Monad m1, Monad m2, MonadTrans t) =
(forall a . m1 a - m2 a) - t m1 a - t m2 a

 ?

 Regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com

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

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


[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Heinrich Apfelmus
Limestraël wrote:
 I have some difficulties to see the use of PromptT, because in the tutorial,
 this type is never mentioned, and its operations (Return and :=) are
 instead constructors of ProgramT...
 
 Would you have some concrete examples? Because there I'm a bit lost (since
 the tutorial doesn't match the operational package as it is, because of the
 type PromptT)...

The project page

http://projects.haskell.org/operational/

links to documentation that describes the differences to The
Operational Monad Tutorial, in particular the new  Prompt  and  PromptT
 types. It also links to several examples. Two small examples are also
included in the Haddock documentation.


I'd like to make it very accessible, so please don't hesitate to report
any difficulties with finding and understanding documentation and examples!


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Fwd: [Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Limestraël
Okay, I just understood that 'Prompt' was just a sort of view for 'Program'.


I'd like to make it very accessible, so please don't hesitate to report
any difficulties with finding and understanding documentation and examples!

Then I think the name 'Prompt' may be misleading for those who doesn't know
the MonadPrompt package. Maybe something like 'ProgramView' ?


 What have we achieved? Both players still can only access functions from
 whatever monad m turns out to be. But now each strategy can pile its own
 custom monad stack on the  Player m  monad! And of course, the use of
 the m Monad is completely optional.

Of course, the custom monad stack has to provide a projection back to
the  Player m a  type

   runMyStackT :: MyStackT (Player m) a - Player m a

According to what Bertram said, each strategy can pile its own custom monad
stack ON the (Player m) monad.
Here, you are stacking the (Player m) monad ON the custom monad stack.
What is then the use of the 'm', in (Player *m*)? Is it not supposed to be a
custom monad? (MonadIO for human, Identity for AI, etc.)

But then, I don't see how the game function could work:

 game :: Monad m = Player m () - Player m () - m ()
As it is written, it requires both players to run in the SAME monad.
And if have a network player ( e.g.* Player (StateT Handle IO)* ) and an AI
storing former opponent's moves ( e.g. *(Monad m) = Player (StateT [Move]
m)* ), then they can't be in the same monad...
*
*
2010/4/14 Heinrich Apfelmus apfel...@quantentunnel.de

 Limestraël wrote:

  I have some difficulties to see the use of PromptT, because in the
 tutorial,
  this type is never mentioned, and its operations (Return and :=) are
  instead constructors of ProgramT...
 
  Would you have some concrete examples? Because there I'm a bit lost
 (since
  the tutorial doesn't match the operational package as it is, because of
 the
  type PromptT)...

 The project page

http://projects.haskell.org/operational/

 links to documentation that describes the differences to The
 Operational Monad Tutorial, in particular the new  Prompt  and  PromptT
  types. It also links to several examples. Two small examples are also
 included in the Haddock documentation.


 I'd like to make it very accessible, so please don't hesitate to report
 any difficulties with finding and understanding documentation and examples!


 Regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com

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

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


Re: Fwd: [Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Bertram Felgenhauer
Limestraël wrote:
 Okay, I just understood that 'Prompt' was just a sort of view for 'Program'.

Right.

runMyStackT :: MyStackT (Player m) a - Player m a
 
 According to what Bertram said, each strategy can pile its own custom monad
 stack ON the (Player m) monad.

Yes, and I meant what Heinrich wrote, you wrap some transformer around
the common Player m monad.

  game :: Monad m = Player m () - Player m () - m ()
 As it is written, it requires both players to run in the SAME monad.
 And if have a network player ( e.g.* Player (StateT Handle IO)* ) and an AI
 storing former opponent's moves ( e.g. *(Monad m) = Player (StateT [Move]
 m)* ), then they can't be in the same monad...

The idea is to pick m = IO, and then use

  type NetPlayer a = StateT Handle (Player IO) a

and

  type AIPlayer a = StateT [Move] (Player IO) a

or possibly

  type AIPlayer a = StateT [Move] (Player Identity) a

using the mapPlayerM (or mapMonad as suggested by Heinrich) function.

You'd then provide functions like

runAIPlayer :: AIPlayer a - Player IO a
runAIPlayer player = {- mapMonad (return . runIdentity) $ -}
evalStateT player []

This gives you most of what you want: You can add custom state and the
like to each player. You can not hope to exchange the base monad m,
because then the 'game' function would have to know how to run both
of those base monads simultaneously. A function like mapMonad is the
best device you can hope for, I think.

regards,

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


Re: Fwd: [Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Limestraël
Okay, I start to understand better...

Just, Heinrich, how would implement the mapMonad function in terms of the
operational package?
You just shown the signature.

2010/4/14 Bertram Felgenhauer bertram.felgenha...@googlemail.com

 Limestraėl wrote:
  Okay, I just understood that 'Prompt' was just a sort of view for
 'Program'.

 Right.

 runMyStackT :: MyStackT (Player m) a - Player m a
 
  According to what Bertram said, each strategy can pile its own custom
 monad
  stack ON the (Player m) monad.

 Yes, and I meant what Heinrich wrote, you wrap some transformer around
 the common Player m monad.

   game :: Monad m = Player m () - Player m () - m ()
  As it is written, it requires both players to run in the SAME monad.
  And if have a network player ( e.g.* Player (StateT Handle IO)* ) and an
 AI
  storing former opponent's moves ( e.g. *(Monad m) = Player (StateT
 [Move]
  m)* ), then they can't be in the same monad...

 The idea is to pick m = IO, and then use

  type NetPlayer a = StateT Handle (Player IO) a

 and

  type AIPlayer a = StateT [Move] (Player IO) a

 or possibly

  type AIPlayer a = StateT [Move] (Player Identity) a

 using the mapPlayerM (or mapMonad as suggested by Heinrich) function.

 You'd then provide functions like

runAIPlayer :: AIPlayer a - Player IO a
runAIPlayer player = {- mapMonad (return . runIdentity) $ -}
evalStateT player []

 This gives you most of what you want: You can add custom state and the
 like to each player. You can not hope to exchange the base monad m,
 because then the 'game' function would have to know how to run both
 of those base monads simultaneously. A function like mapMonad is the
 best device you can hope for, I think.

 regards,

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

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


[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-09 Thread Heinrich Apfelmus
Gwern Branwen wrote:
 Yves Parès limestr...@gmail.com wrote:
 [...]
 But when running the game, the program cannot switch from a player's monad
 to another.

 Do you have any suggestion?
 
 Your desires remind me of the MonadPrompt package
 http://hackage.haskell.org/package/MonadPrompt, which IIRC, has been
 used in some game demos to provide abstraction from IO/test
 harness/pure AI etc.

The game demo can be found by chasing links from the package documentation:

   http://int-e.home.tlink.de/haskell/solitaire.tar.gz


There's also my package operational

   http://hackage.haskell.org/package/operational

which implements the same concept. It's throughly explained here:

   http://apfelmus.nfshost.com/articles/operational-monad.html
   http://projects.haskell.org/operational/


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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