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

2010-04-14 Thread Limestraël
Yves, that is exactly how I designed my program so far.
Human player needs a monad IO, AI needs just a monad, whatever it is, and I
make both run in IO.

And, as you said, the type of the ai (bot :: Monad m = Player m) contains
no IO, so I know that, even if I make it run in IO, it won't make any
side-effect.

My problem was, for example, if I want a player to run in its OWN monad.
Human uses IO, which is unique and shared by all the human players in the
program.
But what if I want an AI that remember every former opponent's move, so that
it could adapt its reflexion all along the game?
Then this AI would have to run in its own State monad, for instance.

2010/4/13 Tillmann Rendel ren...@informatik.uni-marburg.de

 Yves Parès wrote:

 data Player m = Player {
plName :: String,  -- unique for each player
plTurn :: GameGrid - m Move  -- called whenever the player must play
 }


  What I try to avoid is having every player running in IO monad.


 One could define the following players.

  human :: MonadIO m = Player m
  human = ...

  bot :: Monad m = Player m
  bot = ...

 Note that these players are polymorphic in m, only assuming some minimal
 interface.

 Now you can run both players in a single monad which is good enough for
 both, because it supports the union of the interfaces assumed by the various
 players. In this case, this monad could be IO, since it supports both
 MonadIO and Monad.

  changeBoard :: Board - Move - board
  changeBoard = ...

  play :: Player IO - Player IO - GameGrid - IO GameResult
  play p1 p2 board do
move - plTurn p1 board
play p2 p1 (changeBoard board move)

 While this is probably not as expressive as what you want, it is reasonably
 simple, and it has the property that bot is not in the IO monad.

 I have first seen this pattern in monadic interpreters, where you could
 have types like the following.

  eval :: (MonadReader Env m) = Expression - m Value
  exec :: (MonadReader Env m, MonadIO m) = Statement - m ()

 These types reflect that the interpreted language permits side-effects
 only in statements, but not in expressions. This is similar to your
 situation: You want your types to reflect that your game permits
 side-effects only in human players, not in artifical intelligences.

  Tillmann

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


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

2010-04-14 Thread Reid Barton
On Wed, Apr 14, 2010 at 04:43:20PM +0200, Limestraël wrote:
 Yves, that is exactly how I designed my program so far.
 Human player needs a monad IO, AI needs just a monad, whatever it is, and I
 make both run in IO.
 
 And, as you said, the type of the ai (bot :: Monad m = Player m) contains
 no IO, so I know that, even if I make it run in IO, it won't make any
 side-effect.
 
 My problem was, for example, if I want a player to run in its OWN monad.
 Human uses IO, which is unique and shared by all the human players in the
 program.
 But what if I want an AI that remember every former opponent's move, so that
 it could adapt its reflexion all along the game?
 Then this AI would have to run in its own State monad, for instance.

Perhaps the techniques of this recent draft paper would be useful:
http://tomschrijvers.blogspot.com/2010/03/bruno-oliveira-and-i-are-working-on.html
(click the link draft)

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


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

2010-04-13 Thread Bertram Felgenhauer
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

The core game logic would be provided by functions

initGame :: Monad m = m Game
initGame = undefined

makeMove :: Monad m = Move - Game - m Game
makeMove = undefined

To run a game we need to mediate between the two players, performing
their moves. To make this easier we turn the Player's program
into a list of actions. (This is essentially the Prompt type of the
operational package.)

data Program p a where
Return :: a - Program p a
Then   :: p b - (b - Program p a) - Program p a
  
programView :: Prompt p a - Program p a
programView = runPromptC Return Then

game :: Monad m = Player m () - Player m () - m ()
game first second = do
g - initGame
let first'  = programView first
second' = programView second
go :: Monad m
   = Game   -- current state
   - Program (Request m) () -- player 1
   - Program (Request m) () -- player 2
   - m ()
go g (Return _)   pl2 =
return ()
go g (Then (Lift l) pl1)  pl2 =
l = \a - go g (pl1 a) pl2
go g (Then Board pl1) pl2 =
go g (pl1 g) pl2
go g (Then (MakeMove mv) pl1) pl2 =
makeMove mv g = \g - go g pl2 (pl1 ())
go g first' second'

Note that MakeMove swaps the two players.

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.

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.

HTH,

Bertram (aka int-e)


P.S. this is what 'game' would look like without the intermediate
'Program' type, using bare continuations instead:

newtype Pl m = Pl {
 runPl :: Pl m  -- other player
   - Game  -- current game state
   - m ()
}

gameC :: Monad m = Player m () - Player m () - m ()
gameC first second = do
g - initGame
let pl1 = runPromptC ret handle first
pl2 = runPromptC ret handle second
ret _ = Pl $ \_ _ - return ()
handle :: Monad m = Request m a - (a - Pl m) - Pl m
handle (Lift l)  pl1 =
Pl $ \pl2 g - l = \a - runPl (pl1 a) pl2 g
handle Board pl1 =
Pl $ \pl2 g - runPl (pl1 g) pl2 g
handle (MakeMove mv) pl1 =
Pl $ \pl2 g - runPl pl2 (pl1 ()) = makeMove mv g
runPl pl1 pl2 = initGame
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-04-13 Thread Tillmann Rendel

Yves Parès wrote:

data Player m = Player {
plName :: String,  -- unique for each player
plTurn :: GameGrid - m Move  -- called whenever the player must play
}



What I try to avoid is having every player running in IO monad.


One could define the following players.

  human :: MonadIO m = Player m
  human = ...

  bot :: Monad m = Player m
  bot = ...

Note that these players are polymorphic in m, only assuming some minimal 
interface.


Now you can run both players in a single monad which is good enough for 
both, because it supports the union of the interfaces assumed by the 
various players. In this case, this monad could be IO, since it supports 
both MonadIO and Monad.


  changeBoard :: Board - Move - board
  changeBoard = ...

  play :: Player IO - Player IO - GameGrid - IO GameResult
  play p1 p2 board do
move - plTurn p1 board
play p2 p1 (changeBoard board move)

While this is probably not as expressive as what you want, it is 
reasonably simple, and it has the property that bot is not in the IO monad.


I have first seen this pattern in monadic interpreters, where you could 
have types like the following.


  eval :: (MonadReader Env m) = Expression - m Value
  exec :: (MonadReader Env m, MonadIO m) = Statement - m ()

These types reflect that the interpreted language permits side-effects
only in statements, but not in expressions. This is similar to your 
situation: You want your types to reflect that your game permits 
side-effects only in human players, not in artifical intelligences.


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


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

2010-04-10 Thread Yves Parès

Thanks,
I looked at the operational package (since it seemed simpler).
I see its interest when building sets of operations.
I think I see how I could apply it to my current problem. I saw in the
tutorial the sentence: The ability to write multiple interpreters is also
very useful for implementing games, specifically to account for both human
and computer opponents as well as replaying a game from a script.
So I'm supposed to write 2 functions, one interpretHuman (running in IO, and
prompting the user), and one interpretAI (running in Identity)?

Are there examples of such games using operational?


Heinrich Apfelmus wrote:
 
 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
 
 


-
Yves Parès

Live long and prosper
-- 
View this message in context: 
http://old.nabble.com/Simple-game%3A-a-monad-for-each-player-tp28183930p28201466.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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

2010-04-10 Thread Yves Parès

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).


Yves Parès wrote:
 
 Thanks,
 I looked at the operational package (since it seemed simpler).
 I see its interest when building sets of operations.
 I think I see how I could apply it to my current problem. I saw in the
 tutorial the sentence: The ability to write multiple interpreters is also
 very useful for implementing games, specifically to account for both human
 and computer opponents as well as replaying a game from a script.
 So I'm supposed to write 2 functions, one interpretHuman (running in IO,
 and prompting the user), and one interpretAI (running in Identity)?
 
 Are there examples of such games using operational?
 
 
 Heinrich Apfelmus wrote:
 
 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
 
 
 
 


-
Yves Parès

Live long and prosper
-- 
View this message in context: 
http://old.nabble.com/Simple-game%3A-a-monad-for-each-player-tp28183930p28201834.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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

2010-04-10 Thread Philippa Cowderoy

On 10/04/2010 13:57, 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).

   


Make them polymorphic - the human player in any MonadIO, the AI player 
in any monad. Then run them both in the same monad, with some kind of 
wrapping function around the calls setting a context for the appropriate 
player.


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


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

2010-04-10 Thread Yves Parès

Okay for IA, which doesn't need any special monad, but what if I want to make
a network player ?
It would have to run in a State monad, accessing to IO, storing a
ByteString.
For instance, (Monad m) = StateT ByteString m.
The ByteString is a lazy one, we read from it to get the data sent by the
real player through the network.

Then, if I want to have a human an a network player playing sequentially,
how can I do this without stacking each player's monad? (See my first mail)


Philippa Cowderoy wrote:
 
 On 10/04/2010 13:57, 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).


 
 Make them polymorphic - the human player in any MonadIO, the AI player 
 in any monad. Then run them both in the same monad, with some kind of 
 wrapping function around the calls setting a context for the appropriate 
 player.
 
 -- 
 fli...@flippac.org
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 


-
Yves Parès

Live long and prosper
-- 
View this message in context: 
http://old.nabble.com/Simple-game%3A-a-monad-for-each-player-tp28183930p28204685.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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

2010-04-08 Thread Yves Parès

Hello Cafe,

I have a question about program design.
Let's say I have a simple sequential game (a TicTacToe for instance, but
with more than 2 players).
I have a Player datatype which is like:

data Player m = Player {
plName :: String,  -- unique for each player
plTurn :: GameGrid - m Move  -- called whenever the player must play
}

As you may guess, the 'm' type variable is intended to be a Monad.
The goal is that every player has his own monad. For instance :
- a human player needs to interact with the program, so its monad would be
IO, or an instance of MonadIO.
- a network player, which transparently sends the game state and receives
moves through network, must also have access to IO to play.
- an AI doesn't need to interact with the outside of the program, so its
monad can be the one we want (e.g. Identity).

First, do you think it is a good way to design the program?
I want the game to be totally independent of the players who are currently
playing. They can be humans, AIs, AIs and network players and humans, and so
on.

But when running the game, the program cannot switch from a player's monad
to another.
If we want every player to run in his own monad, I think we have to stack
every players' monad, and lift their actions each time they have to play.
This is not a problem, the sole condition now is that every player has type:
(Monad m, MonadTrans m) = Player m.

But I think it's a little bit of overkill, and it may be a little bit
complicated to implement such a thing.
What I try to avoid is having every player running in IO monad.

Do you have any suggestion?

-
Yves Parès

Live long and prosper
-- 
View this message in context: 
http://old.nabble.com/Simple-game%3A-a-monad-for-each-player-tp28183930p28183930.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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

2010-04-08 Thread Gwern Branwen
On Thu, Apr 8, 2010 at 4:08 PM, Yves Parès limestr...@gmail.com wrote:

 Hello Cafe,

 I have a question about program design.
 Let's say I have a simple sequential game (a TicTacToe for instance, but
 with more than 2 players).
 I have a Player datatype which is like:

 data Player m = Player {
    plName :: String,  -- unique for each player
    plTurn :: GameGrid - m Move  -- called whenever the player must play
 }

 As you may guess, the 'm' type variable is intended to be a Monad.
 The goal is that every player has his own monad. For instance :
 - a human player needs to interact with the program, so its monad would be
 IO, or an instance of MonadIO.
 - a network player, which transparently sends the game state and receives
 moves through network, must also have access to IO to play.
 - an AI doesn't need to interact with the outside of the program, so its
 monad can be the one we want (e.g. Identity).

 First, do you think it is a good way to design the program?
 I want the game to be totally independent of the players who are currently
 playing. They can be humans, AIs, AIs and network players and humans, and so
 on.

 But when running the game, the program cannot switch from a player's monad
 to another.
 If we want every player to run in his own monad, I think we have to stack
 every players' monad, and lift their actions each time they have to play.
 This is not a problem, the sole condition now is that every player has type:
 (Monad m, MonadTrans m) = Player m.

 But I think it's a little bit of overkill, and it may be a little bit
 complicated to implement such a thing.
 What I try to avoid is having every player running in IO monad.

 Do you have any suggestion?

 -
 Yves Parès

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.

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