[Haskell-cafe] Re: An interesting monad: "Prompt"

apfelmus apfelmus at quantentunnel.de
Wed Nov 21 07:03:25 EST 2007


Ryan Ingram wrote:
> I've been trying to implement a few rules-driven board/card games in Haskell
> and I always run into the ugly problem of "how do I get user input"?
> 
> The usual technique is to embed the game in the IO Monad:
> 
> The problem with this approach is that now arbitrary IO computations are
> expressible as part of a game action, which makes it much harder to
> implement things like replay, undo, and especially testing!
> 
> The goal was to be able to write code like this:
> 
> ] takeTurn :: Player -> Game ()
> ] takeTurn player = do
> ]     piece  <- action (ChoosePiece player)
> ]     attack <- action (ChooseAttack player piece)
> ]     bonusTurn <- executeAttack piece attack
> ]     when bonusTurn $ takeTurn player
> 
> but be able to script the code for testing, allow undo, automatically
> be able to save replays, etc.
> 
> While thinking about this problem earlier this week, I came up with the
> following solution:
> 
>> class Monad m => MonadPrompt p m | m -> p where
>>    prompt :: p a -> m a
> 
> "prompt" is an action that takes a prompt type and gives you a result.
> 
> A simple example:
> ] prompt [1,3,5] :: MonadPrompt [] m => m Int
> 
> This prompt would ask for someone to pick a value from the list and return
> it.
> This would be somewhat useful on its own; you could implement a "choose"
> function that picked randomly from a list of options and gave
> non-deterministic (or even exhaustive) testing, but on its own this wouldn't
> be much better than the list monad.
> [...]
>> data Prompt (p :: * -> *) :: (* -> *) where
>>     PromptDone :: result -> Prompt p result
>>     -- a is the type needed to continue the computation
>>     Prompt :: p a -> (a -> Prompt p result) -> Prompt p result
> 
> Intuitively, a (Prompt p result) either gives you an immediate result
> (PromptDone), or gives you a prompt which you need to reply to in order to
> continue the computation.
> 
> This type is a MonadPrompt:
> 
>> instance Functor (Prompt p) where
>>    fmap f (PromptDone r) = PromptDone (f r)
>>    fmap f (Prompt p cont) = Prompt p (fmap f . cont)
>>
>> instance Monad (Prompt p) where
>>    return = PromptDone
>>    PromptDone r  >>= f = f r
>>    Prompt p cont >>= f = Prompt p ((>>= f) . cont)
>>
>> instance MonadPrompt p (Prompt p) where
>>    prompt p = Prompt p return

Marvelous!

Basically, by making the continuation (a -> Prompt p result) explicit, 
we have the flexibility to acquire the value  a  differently, like 
through user input or a replay script. The popular continuations for 
implementing web applications in Lisp/Scheme do the same thing.

A slightly different point of view is that you use a term implementation 
for your monad, at least for the interesting primitive effects like

   choosePiece   :: Player -> Game Piece
   chooseAttack  :: Player -> Piece -> Game Attack

By using constructors for them, you have the flexibility to write 
different interpreters for  Game a , like

   play   :: Game a -> IO a
   replay :: Game a -> GameScript -> a

with the semantics

   play (choosePiece pl >>= f) = do
      putStrLn "Player " ++ show pl ++ ", choose your piece:"
      play f . read =<< getLine

   replay (choosePiece pl >>= f) (Piece pl' piece:xs)
      | pl == pl' = replay (f piece) xs

Just for the record, the most general term implementation is presented here

   Chuan-kai Lin. Programming Monads Operationally with Unimo.
   http://web.cecs.pdx.edu/~cklin/papers/unimo-143.pdf


Btw, the web framework WASH/CGI for Haskell uses some kind of prompt 
monad, too.

   Peter Thiemann. An Embedded Domain-Specific Language for
   Type-Safe Server-Side Web-Scripting.
   http://www.informatik.uni-freiburg.de/~thiemann/WASH/draft.pdf

Here, the server replays parts of the CGI monad when the user submits a 
form i.e. answers to a prompt.


Regards,
apfelmus



More information about the Haskell-Cafe mailing list