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

Limestraël limestrael at gmail.com
Wed Apr 14 11:17:38 EDT 2010


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 <apfelmus at 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100414/a56ed9ec/attachment.html


More information about the Haskell-Cafe mailing list