
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