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

2008-01-03 Thread Felipe Lessa
On Nov 18, 2007 10:22 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
[snip]
  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
[snip]
  runPromptM :: Monad m = (forall a. p a - m a) - Prompt p r - m r
  runPromptM _ (PromptDone r) = return r
  runPromptM f (Prompt pa c)  = f pa = runPromptM f . c
[snip]

How can we prove that (runPromptM prompt === id)? I was trying to go with

runPromptM prompt (PromptDone r)
 = return r
 = PromptDone r

runPromptM prompt (Prompt pa c)
 = prompt pa = runPromptM prompt . c
 = Prompt pa return = runPromptM prompt . c
 = Prompt pa ((= (runPromptM prompt . c) . return)
 = Prompt pa (runPromptM prompt . c)

... and I got stuck here. It seems obvious that we can strip out the
'runPromptM prompt' down there to finish the proof, but that doesn't
sound very nice, as I'd need to suppose what I'm trying to prove. Am I
missing something here?

Thank you,

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


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

2007-12-30 Thread Ryan Ingram
Currently, yes; I was experimenting with type families.  But it's pretty
simple to get it to compile on 6.6.1:
- remove the {-# LANGUAGE #-} pragma and replace with {-# OPTIONS_GHC
-fglasgow-exts -fallow-undecidable-instances #-}

- change the class declaration for MonadPrompter from
 class Monad m = MonadPrompter m where
type PromptType m :: * - *
prompt :: PromptType m a - m a

to

 class Monad m = MonadPrompter p m | m - p where
prompt :: p a - m a

- change all the instance declarations from something like this:

 instance MonadPrompter (XXX) where
type PromptType (XXX) = YYY
prompt = ...

to something like this:

 instance MonadPrompter YYY (XXX) where
prompt = ...

 you're done.

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


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

2007-12-29 Thread Ryan Ingram
I posted the current version of this code at
http://ryani.freeshell.org/haskell/

On 12/28/07, Thomas Hartman [EMAIL PROTECTED] wrote:

 Would you mind posting the code for Prompt used by

 import Prompt

 I tried using Prompt.lhs from your first post but it appears to be
 incompatible with the guessing game program when I got tired of
 reading the code and actually tried running it.

 best, thomas.



 2007/12/4, Ryan Ingram [EMAIL PROTECTED]:
  Ask and ye shall receive.  A simple guess-a-number game in MonadPrompt
  follows.
 
  But before I get to that, I have some comments:
 
 
  Serializing the state at arbitrary places is hard; the Prompt contains a
  continuation function so unless you have a way to serialize closures it
  seems like you lose.  But if you have safe points during the execution
 at
  which you know all relevant state is inside your game state, you can
 save
  there by serializing the state and providing a way to restart the
  computation at those safe points.
 
  I haven't looked at MACID at all; what's that?
 
   {-# LANGUAGE GADTs, RankNTypes #-}
   module Main where
   import Prompt
   import Control.Monad.State
   import System.Random (randomRIO)
   import System.IO
   import Control.Exception (assert)
 
  Minimalist functional references implementation.
  In particular, for this example, we skip the really interesting thing:
  composability.
 
  See http://luqui.org/blog/archives/2007/08/05/ for a real
  implementation.
 
   data FRef s a = FRef
 { frGet :: s - a
 , frSet :: a - s - s
 }
 
   fetch :: MonadState s m = FRef s a - m a
   fetch ref = get = return . frGet ref
 
   infix 1 =:
   infix 1 =:
   (=:) :: MonadState s m = FRef s a - a - m ()
   ref =: val = modify $ frSet ref val
   (=:) :: MonadState s m = FRef s a - m a - m ()
   ref =: act = act = modify . frSet ref
   update :: MonadState s m = FRef s a - (a - a) - m ()
   update ref f = fetch ref = \a - ref =: f a
 
  Interactions that a user can have with the game:
 
   data GuessP a where
  GetNumber :: GuessP Int
  Guess :: GuessP Int
  Print :: String - GuessP ()
 
  Game state.
 
  We could do this with a lot less state, but I'm trying to show what's
  possible here.  In fact, for this example it's probably easier to just
  thread the state through the program directly, but bigger games want
 real
  state, so I'm showing how to do that.
 
   data GuessS = GuessS
 { gsNumGuesses_ :: Int
 , gsTargetNumber_ :: Int
 }
 
   -- a real implementation wouldn't do it this way :)
   initialGameState :: GuessS
   initialGameState = GuessS undefined undefined
 
   gsNumGuesses, gsTargetNumber :: FRef GuessS Int
   gsNumGuesses   = FRef gsNumGuesses_   $ \a s - s { gsNumGuesses_   =
 a }
   gsTargetNumber = FRef gsTargetNumber_ $ \a s - s { gsTargetNumber_ =
 a }
 
  Game monad with some useful helper functions
 
   type Game = StateT GuessS (Prompt GuessP)
 
   gPrint :: String - Game ()
   gPrint = prompt . Print
 
   gPrintLn :: String - Game ()
   gPrintLn s = gPrint (s ++ \n)
 
  Implementation of the game:
 
   gameLoop :: Game Int
   gameLoop = do
  update gsNumGuesses (+1)
  guessNum - fetch gsNumGuesses
  gPrint (Guess # ++ show guessNum ++ :)
  guess - prompt Guess
  answer - fetch gsTargetNumber
  
  if guess == answer
then do
  gPrintLn Right!
  return guessNum
else do
  gPrintLn $ concat
  [ You guessed too 
  , if guess  answer then low else high
  , ! Try again.
  ]
  gameLoop
 
   game :: Game ()
   game = do
  gsNumGuesses =: 0
  gsTargetNumber =: prompt GetNumber
  gPrintLn I'm thinking of a number.  Try to guess it!
  numGuesses - gameLoop
  gPrintLn (It took you  ++ show numGuesses ++  guesses!)
 
  Simple unwrapper for StateT that launches the game.
 
   runGame :: Monad m = (forall a. GuessP a - m a) - m ()
   runGame f = runPromptM f (evalStateT game initialGameState)
 
  Here is the magic function for interacting with the player in
 IO.  Exercise
  for the reader: make this more robust.
 
   gameIOPrompt :: GuessP a - IO a
   gameIOPrompt GetNumber = randomRIO (1, 100)
   gameIOPrompt (Print s) = putStr s
   gameIOPrompt Guess = fmap read getLine
 
  If you wanted to add undo, all you have to do is save off the current
 Prompt
  in the middle of runPromptM; you can return to the old state at any
 time.
 
   gameIO :: IO ()
   gameIO = do
   hSetBuffering stdout NoBuffering
   runGame gameIOPrompt
 
  Here's a scripted version.
 
   type GameScript = State [Int]
  
   scriptPrompt :: Int - GuessP a - GameScript a
   scriptPrompt n GetNumber = return n
   scriptPrompt _ (Print _) = return ()
   scriptPrompt _ Guess = do
   (x:xs) - get -- fails if script runs out of answers
   put xs
   return x
  
   scriptTarget :: Int
   scriptTarget = 23
   scriptGuesses :: [Int]
   scriptGuesses = [50, 25, 12, 19, 

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

2007-12-28 Thread Thomas Hartman
Would you mind posting the code for Prompt used by

import Prompt

I tried using Prompt.lhs from your first post but it appears to be
incompatible with the guessing game program when I got tired of
reading the code and actually tried running it.

best, thomas.



2007/12/4, Ryan Ingram [EMAIL PROTECTED]:
 Ask and ye shall receive.  A simple guess-a-number game in MonadPrompt
 follows.

 But before I get to that, I have some comments:


 Serializing the state at arbitrary places is hard; the Prompt contains a
 continuation function so unless you have a way to serialize closures it
 seems like you lose.  But if you have safe points during the execution at
 which you know all relevant state is inside your game state, you can save
 there by serializing the state and providing a way to restart the
 computation at those safe points.

 I haven't looked at MACID at all; what's that?

  {-# LANGUAGE GADTs, RankNTypes #-}
  module Main where
  import Prompt
  import Control.Monad.State
  import System.Random (randomRIO)
  import System.IO
  import Control.Exception (assert)

 Minimalist functional references implementation.
 In particular, for this example, we skip the really interesting thing:
 composability.

 See http://luqui.org/blog/archives/2007/08/05/ for a real
 implementation.

  data FRef s a = FRef
{ frGet :: s - a
, frSet :: a - s - s
}

  fetch :: MonadState s m = FRef s a - m a
  fetch ref = get = return . frGet ref

  infix 1 =:
  infix 1 =:
  (=:) :: MonadState s m = FRef s a - a - m ()
  ref =: val = modify $ frSet ref val
  (=:) :: MonadState s m = FRef s a - m a - m ()
  ref =: act = act = modify . frSet ref
  update :: MonadState s m = FRef s a - (a - a) - m ()
  update ref f = fetch ref = \a - ref =: f a

 Interactions that a user can have with the game:

  data GuessP a where
 GetNumber :: GuessP Int
 Guess :: GuessP Int
 Print :: String - GuessP ()

 Game state.

 We could do this with a lot less state, but I'm trying to show what's
 possible here.  In fact, for this example it's probably easier to just
 thread the state through the program directly, but bigger games want real
 state, so I'm showing how to do that.

  data GuessS = GuessS
{ gsNumGuesses_ :: Int
, gsTargetNumber_ :: Int
}

  -- a real implementation wouldn't do it this way :)
  initialGameState :: GuessS
  initialGameState = GuessS undefined undefined

  gsNumGuesses, gsTargetNumber :: FRef GuessS Int
  gsNumGuesses   = FRef gsNumGuesses_   $ \a s - s { gsNumGuesses_   = a }
  gsTargetNumber = FRef gsTargetNumber_ $ \a s - s { gsTargetNumber_ = a }

 Game monad with some useful helper functions

  type Game = StateT GuessS (Prompt GuessP)

  gPrint :: String - Game ()
  gPrint = prompt . Print

  gPrintLn :: String - Game ()
  gPrintLn s = gPrint (s ++ \n)

 Implementation of the game:

  gameLoop :: Game Int
  gameLoop = do
 update gsNumGuesses (+1)
 guessNum - fetch gsNumGuesses
 gPrint (Guess # ++ show guessNum ++ :)
 guess - prompt Guess
 answer - fetch gsTargetNumber
 
 if guess == answer
   then do
 gPrintLn Right!
 return guessNum
   else do
 gPrintLn $ concat
 [ You guessed too 
 , if guess  answer then low else high
 , ! Try again.
 ]
 gameLoop

  game :: Game ()
  game = do
 gsNumGuesses =: 0
 gsTargetNumber =: prompt GetNumber
 gPrintLn I'm thinking of a number.  Try to guess it!
 numGuesses - gameLoop
 gPrintLn (It took you  ++ show numGuesses ++  guesses!)

 Simple unwrapper for StateT that launches the game.

  runGame :: Monad m = (forall a. GuessP a - m a) - m ()
  runGame f = runPromptM f (evalStateT game initialGameState)

 Here is the magic function for interacting with the player in IO.  Exercise
 for the reader: make this more robust.

  gameIOPrompt :: GuessP a - IO a
  gameIOPrompt GetNumber = randomRIO (1, 100)
  gameIOPrompt (Print s) = putStr s
  gameIOPrompt Guess = fmap read getLine

 If you wanted to add undo, all you have to do is save off the current Prompt
 in the middle of runPromptM; you can return to the old state at any time.

  gameIO :: IO ()
  gameIO = do
  hSetBuffering stdout NoBuffering
  runGame gameIOPrompt

 Here's a scripted version.

  type GameScript = State [Int]
 
  scriptPrompt :: Int - GuessP a - GameScript a
  scriptPrompt n GetNumber = return n
  scriptPrompt _ (Print _) = return ()
  scriptPrompt _ Guess = do
  (x:xs) - get -- fails if script runs out of answers
  put xs
  return x
 
  scriptTarget :: Int
  scriptTarget = 23
  scriptGuesses :: [Int]
  scriptGuesses = [50, 25, 12, 19, 22, 24, 23]

 gameScript is True if the game ran to completion successfully, and False or
 bottom otherwise.
 Try adding or removing numbers from scriptGuesses above and re-running the
 program.

  gameScript :: Bool
  gameScript = null $ execState (runGame (scriptPrompt scriptTarget))
 scriptGuesses


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

2007-12-04 Thread Ryan Ingram
Ask and ye shall receive.  A simple guess-a-number game in MonadPrompt
follows.

But before I get to that, I have some comments:

 Serializing the state at arbitrary places is hard; the Prompt contains a
continuation function so unless you have a way to serialize closures it
seems like you lose.  But if you have safe points during the execution at
which you know all relevant state is inside your game state, you can save
there by serializing the state and providing a way to restart the
computation at those safe points.

I haven't looked at MACID at all; what's that?

 {-# LANGUAGE GADTs, RankNTypes #-}
 module Main where
 import Prompt
 import Control.Monad.State
 import System.Random (randomRIO)
 import System.IO
 import Control.Exception (assert)

Minimalist functional references implementation.
In particular, for this example, we skip the really interesting thing:
composability.

See http://luqui.org/blog/archives/2007/08/05/ for a real implementation.

 data FRef s a = FRef
   { frGet :: s - a
   , frSet :: a - s - s
   }

 fetch :: MonadState s m = FRef s a - m a
 fetch ref = get = return . frGet ref

 infix 1 =:
 infix 1 =:
 (=:) :: MonadState s m = FRef s a - a - m ()
 ref =: val = modify $ frSet ref val
 (=:) :: MonadState s m = FRef s a - m a - m ()
 ref =: act = act = modify . frSet ref
 update :: MonadState s m = FRef s a - (a - a) - m ()
 update ref f = fetch ref = \a - ref =: f a

Interactions that a user can have with the game:

 data GuessP a where
GetNumber :: GuessP Int
Guess :: GuessP Int
Print :: String - GuessP ()

Game state.

We could do this with a lot less state, but I'm trying to show what's
possible here.  In fact, for this example it's probably easier to just
thread the state through the program directly, but bigger games want real
state, so I'm showing how to do that.

 data GuessS = GuessS
   { gsNumGuesses_ :: Int
   , gsTargetNumber_ :: Int
   }

 -- a real implementation wouldn't do it this way :)
 initialGameState :: GuessS
 initialGameState = GuessS undefined undefined

 gsNumGuesses, gsTargetNumber :: FRef GuessS Int
 gsNumGuesses   = FRef gsNumGuesses_   $ \a s - s { gsNumGuesses_   = a }
 gsTargetNumber = FRef gsTargetNumber_ $ \a s - s { gsTargetNumber_ = a }

Game monad with some useful helper functions

 type Game = StateT GuessS (Prompt GuessP)

 gPrint :: String - Game ()
 gPrint = prompt . Print

 gPrintLn :: String - Game ()
 gPrintLn s = gPrint (s ++ \n)

Implementation of the game:

 gameLoop :: Game Int
 gameLoop = do
update gsNumGuesses (+1)
guessNum - fetch gsNumGuesses
gPrint (Guess # ++ show guessNum ++ :)
guess - prompt Guess
answer - fetch gsTargetNumber

if guess == answer
  then do
gPrintLn Right!
return guessNum
  else do
gPrintLn $ concat
[ You guessed too 
, if guess  answer then low else high
, ! Try again.
]
gameLoop

 game :: Game ()
 game = do
gsNumGuesses =: 0
gsTargetNumber =: prompt GetNumber
gPrintLn I'm thinking of a number.  Try to guess it!
numGuesses - gameLoop
gPrintLn (It took you  ++ show numGuesses ++  guesses!)

Simple unwrapper for StateT that launches the game.

 runGame :: Monad m = (forall a. GuessP a - m a) - m ()
 runGame f = runPromptM f (evalStateT game initialGameState)

Here is the magic function for interacting with the player in IO.  Exercise
for the reader: make this more robust.

 gameIOPrompt :: GuessP a - IO a
 gameIOPrompt GetNumber = randomRIO (1, 100)
 gameIOPrompt (Print s) = putStr s
 gameIOPrompt Guess = fmap read getLine

If you wanted to add undo, all you have to do is save off the current Prompt
in the middle of runPromptM; you can return to the old state at any time.

 gameIO :: IO ()
 gameIO = do
 hSetBuffering stdout NoBuffering
 runGame gameIOPrompt

Here's a scripted version.

 type GameScript = State [Int]

 scriptPrompt :: Int - GuessP a - GameScript a
 scriptPrompt n GetNumber = return n
 scriptPrompt _ (Print _) = return ()
 scriptPrompt _ Guess = do
 (x:xs) - get -- fails if script runs out of answers
 put xs
 return x

 scriptTarget :: Int
 scriptTarget = 23
 scriptGuesses :: [Int]
 scriptGuesses = [50, 25, 12, 19, 22, 24, 23]

gameScript is True if the game ran to completion successfully, and False or
bottom otherwise.
Try adding or removing numbers from scriptGuesses above and re-running the
program.

 gameScript :: Bool
 gameScript = null $ execState (runGame (scriptPrompt scriptTarget))
scriptGuesses

 main = do
assert gameScript $ return ()
gameIO
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-12-04 Thread Thomas Hartman
Thank you!

I really appreciate your explanation, and I hope this will enable me
to do some interesting and usefull stuff, in addition to firming up my
understanding of some of the more advanced haskell type system
features.

MACID is a sort of RDBMS replacement used as a backend by the HAppS
web framework.

To quote from http://www.haskell.org/communities/05-2007/html/report.html

Apps as Simple State Transformers

HAppS keeps your application development very simple. You represent
state with the Haskell data structure you find most natural for that
purpose. Your app then is just a set of state transformer functions
(in the MACID Monad) that take an event and state as input and that
evaluate to a new state, a response, and a (possibly null) set of
sideeffects.

It sounds great, but in practice it is not that simple to use, largely
because HAppS is in such a state of flux right now that even
installing the current codebase is pretty daunting.

However, I think a simple example of using MACID to guess a number
would be a great piece of documentation, and it might even be a step
towards using HAppS/MACID to easily do things other than serve web
apps. (HAppS is meant to be a general application serving framework,
but all the docu is oriented towards serving web pages, and even that
documentation is pretty shaky.)

What I ultimately would like to do is adapt this guess a number stuff
to HAppS/MACID so it is an example server for a multi-user console app
with this cool undo/replay/logging functionality which can then be
plugged into more sophisticated uses. Porting the console app to a web
app would be a further step. Hopefully, since all the state stuff has
been so meticulously compartmentalized it's easy and obvious how to do
this, just a matter of changing the IO to be outputting html rather
than console text. That is the HAppS tutorial I would like to see.

thomas.

2007/12/4, Ryan Ingram [EMAIL PROTECTED]:
 Ask and ye shall receive.  A simple guess-a-number game in MonadPrompt
 follows.

 But before I get to that, I have some comments:


 Serializing the state at arbitrary places is hard; the Prompt contains a
 continuation function so unless you have a way to serialize closures it
 seems like you lose.  But if you have safe points during the execution at
 which you know all relevant state is inside your game state, you can save
 there by serializing the state and providing a way to restart the
 computation at those safe points.

 I haven't looked at MACID at all; what's that?

  {-# LANGUAGE GADTs, RankNTypes #-}
  module Main where
  import Prompt
  import Control.Monad.State
  import System.Random (randomRIO)
  import System.IO
  import Control.Exception (assert)

 Minimalist functional references implementation.
 In particular, for this example, we skip the really interesting thing:
 composability.

 See http://luqui.org/blog/archives/2007/08/05/ for a real
 implementation.

  data FRef s a = FRef
{ frGet :: s - a
, frSet :: a - s - s
}

  fetch :: MonadState s m = FRef s a - m a
  fetch ref = get = return . frGet ref

  infix 1 =:
  infix 1 =:
  (=:) :: MonadState s m = FRef s a - a - m ()
  ref =: val = modify $ frSet ref val
  (=:) :: MonadState s m = FRef s a - m a - m ()
  ref =: act = act = modify . frSet ref
  update :: MonadState s m = FRef s a - (a - a) - m ()
  update ref f = fetch ref = \a - ref =: f a

 Interactions that a user can have with the game:

  data GuessP a where
 GetNumber :: GuessP Int
 Guess :: GuessP Int
 Print :: String - GuessP ()

 Game state.

 We could do this with a lot less state, but I'm trying to show what's
 possible here.  In fact, for this example it's probably easier to just
 thread the state through the program directly, but bigger games want real
 state, so I'm showing how to do that.

  data GuessS = GuessS
{ gsNumGuesses_ :: Int
, gsTargetNumber_ :: Int
}

  -- a real implementation wouldn't do it this way :)
  initialGameState :: GuessS
  initialGameState = GuessS undefined undefined

  gsNumGuesses, gsTargetNumber :: FRef GuessS Int
  gsNumGuesses   = FRef gsNumGuesses_   $ \a s - s { gsNumGuesses_   = a }
  gsTargetNumber = FRef gsTargetNumber_ $ \a s - s { gsTargetNumber_ = a }

 Game monad with some useful helper functions

  type Game = StateT GuessS (Prompt GuessP)

  gPrint :: String - Game ()
  gPrint = prompt . Print

  gPrintLn :: String - Game ()
  gPrintLn s = gPrint (s ++ \n)

 Implementation of the game:

  gameLoop :: Game Int
  gameLoop = do
 update gsNumGuesses (+1)
 guessNum - fetch gsNumGuesses
 gPrint (Guess # ++ show guessNum ++ :)
 guess - prompt Guess
 answer - fetch gsTargetNumber
 
 if guess == answer
   then do
 gPrintLn Right!
 return guessNum
   else do
 gPrintLn $ concat
 [ You guessed too 
 , if guess  answer then low else high
 , ! Try again.
 ]
 gameLoop

  game :: Game ()
  game 

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

2007-12-03 Thread Thomas Hartman
I've been playing with MonadPrompt for about ten days now, trying to get 
it to do something useful for me.

Specifically, I'm trying to implement guess a number since that's the 
hello world of haskell state programs, or so it seems to me. I want to 
have this with scripting / replay / undo and the other goodies claimed 
possible

http://thomashartman-learning.googlecode.com/svn/trunk/haskell/guessANumber

It's been slow going due to still getting to grips with GADTs and other 
more advanced features of the typing system.

If Ryan (or anyone) would care to share any working code for a simple game 
that uses MonadPrompt, ideally with scripting / replay / undo that would 
be extremely helpful.

Otherwise I'll be back with more specific questions about my attempts to 
use this stuff soon enough :)

(At present, that;'s just trying to get some of the more interesting code 
you posted as untested to compile.)

For what it's worth, my game currently saves high some (but not all) 
state-y information in a serialized form to track high scores. If I can 
get this working with MonadPrompt, my next quest will be to use MACID to 
do the serialization instead, and then *all* state will be saved if I 
understand correctly.

t.




Ryan Ingram [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
11/18/2007 07:22 PM

To
haskell haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] An interesting monad: Prompt






(This message is a literate haskell file.  Code for the Prompt monad is
preceded by ; code for my examples is preceded by ] and isn't 
complete, 
but intended for illustration.)

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: 

] type Game = IO
] -- or
] type Game = StateT GameState IO

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:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances  #-}
 -- undecidable instances is only needed for the MonadTrans instance 
below 

 module Prompt where
 import Control.Monad.Trans
 import Control.Monad.Identity

 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.

What really made this click for me was that the prompt type could be built 

on a GADT:

] newtype GamePrompt a = GP (GameState, GameChoice a)
] data GameChoice a where
]-- pick a piece to act with
]ChoosePiece :: Player - GameChoice GamePiece
]-- pick how they should attack 
]ChooseAttack :: Player - GamePiece - GameChoice AttackType
]-- etc.

Now you can use this type information as part of a handler function:
] gameIO :: GamePrompt a - IO a
] gameIO (GP (state, ChoosePiece player)) = getPiece state player
] gameIO (GP (state, ChooseAttack player piece)) = attackMenu player piece
] -- ...

The neat thing here is that the GADT specializes the type of IO a on the 

right hand side.  So, getPiece state player has the type IO GamePiece, 
not
the general IO a.  So the GADT is serving as a witness of the type of
response wanted by the game.

Another neat things is that, you don't need to embed this in the IO monad 
at
all; you could instead run a pure computation to do AI, or even use it for
unit testing!

 -- unit testing example
 data ScriptElem p where SE :: p a - a - ScriptElem p 
 type Script p = [ScriptElem p]

 infix 1 --
 (--) = SE


] gameScript :: ScriptElem GameChoice - GameChoice a - Maybe a
] gameScript (SE (ChoosePiece _)piece)  (ChoosePiece _)= Just 
piece 
] gameScript (SE (ChooseAttack _ _) attack) (ChooseAttack _ _) = Just 
attack
] gameScript _  _  = Nothing
]
] testGame :: Script GameChoice
] testGame =
]   [ ChoosePiece  P1-- Knight 
]   , ChooseAttack P1 Knight -- Charge
]   , ChoosePiece  P2-- FootSoldier
]   , ...
]   ]

So, how to implement all

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

2007-11-25 Thread Ryan Ingram
Also, I didn't realize this at first, but in order to use any of the
MonadTrans instances, like having StateT s (Prompt p) automatically be a
MonadPrompt, you sadly also need -fallow-overlapping-instances.

This is because MonadTrans monads looks a lot like Prompt.

arbitrary MonadTrans monad:
  t (m :: * - *) (a :: *)
Prompt:
  Prompt (p :: * - *) (a :: *)

Since you can substitute Prompt for t and rename m to p, they look like
they match the some of the same types to the compiler.  However, since
Prompt won't ever be declared as an instance of MonadTrans, the overlap is
safe.

The alternative is to declare all the instances you need manually:

instance MonadPrompt p (StateT s (Prompt p)) where prompt = lift . prompt
-- etc.

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


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

2007-11-24 Thread Thomas Hartman
Looks very cool. So I tried playing with this code, unfortunately
couldn't get it to compile.

Could you double check that what you posted compiles, and if it does,
any idea what I'm doing wrong?

This is with

 {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

thanks, t.

Prelude :r
[1 of 1] Compiling Prompt   ( prompt.lhs, interpreted )

prompt.lhs:140:1:
Could not deduce (Monad tm)
  from the context (Monad (t m), MonadTrans t, MonadPrompt p m)
  arising from the superclasses of an instance declaration
  at prompt.lhs:140:1
Possible fix:
  add (Monad tm) to the instance declaration superclass context
In the instance declaration for `MonadPrompt p tm'

prompt.lhs:141:13:
Couldn't match expected type `tm' (a rigid variable)
   against inferred type `t1 m1'
  `tm' is bound by the instance declaration at prompt.lhs:140:1
  Expected type: p a - tm a
  Inferred type: p a - t1 m1 a
In the expression: lift . prompt
In the definition of `prompt': prompt = lift . prompt
Failed, modules loaded: none.

This is around

 -- Just for fun, make it work with StateT as well
 -- (needs -fallow-undecidable-instances)

 instance (Monad (t m), MonadTrans t, MonadPrompt p m) = MonadPrompt p (tm) 
 where
prompt = lift . prompt



2007/11/18, Ryan Ingram [EMAIL PROTECTED]:
 (This message is a literate haskell file.  Code for the Prompt monad is
 preceded by ; code for my examples is preceded by ] and isn't complete,
 but intended for illustration.)

 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:

 ] type Game = IO
 ] -- or
 ] type Game = StateT GameState IO

 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:

  {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances
  #-}
  -- undecidable instances is only needed for the MonadTrans instance below
 
  module Prompt where
  import Control.Monad.Trans
  import Control.Monad.Identity

  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.

 What really made this click for me was that the prompt type could be built
 on a GADT:

 ] newtype GamePrompt a = GP (GameState, GameChoice a)
 ] data GameChoice a where
 ]-- pick a piece to act with
 ]ChoosePiece :: Player - GameChoice GamePiece
 ]-- pick how they should attack
 ]ChooseAttack :: Player - GamePiece - GameChoice AttackType
 ]-- etc.

 Now you can use this type information as part of a handler function:
 ] gameIO :: GamePrompt a - IO a
  ] gameIO (GP (state, ChoosePiece player)) = getPiece state player
 ] gameIO (GP (state, ChooseAttack player piece)) = attackMenu player piece
 ] -- ...

 The neat thing here is that the GADT specializes the type of IO a on the
 right hand side.  So, getPiece state player has the type IO GamePiece,
 not
 the general IO a.  So the GADT is serving as a witness of the type of
 response wanted by the game.

 Another neat things is that, you don't need to embed this in the IO monad at
 all; you could instead run a pure computation to do AI, or even use it for
 unit testing!

  -- unit testing example
  data ScriptElem p where SE :: p a - a - ScriptElem p
  type Script p = [ScriptElem p]
 
  infix 1 --
  (--) = SE


 ] gameScript :: ScriptElem GameChoice - GameChoice a - Maybe a
 ] gameScript (SE (ChoosePiece _)piece)  (ChoosePiece _)= Just piece
 ] gameScript (SE (ChooseAttack _ _) attack) (ChooseAttack _ _) = Just attack
 ] gameScript _  _
= Nothing
 ]
 ] testGame :: Script GameChoice
 ] testGame =
 ]   [ ChoosePiece  P1-- Knight
 ]   , ChooseAttack P1 Knight -- Charge
 ]   , ChoosePiece  P2-- FootSoldier
 ]   , ...
 ]   ]

 So, how to implement all of this?

  data Prompt (p 

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

2007-11-24 Thread Thomas Hartman
fwiw, if I comment those two lines around 141 out, it compiles.

t.

2007/11/24, Thomas Hartman [EMAIL PROTECTED]:
 Looks very cool. So I tried playing with this code, unfortunately
 couldn't get it to compile.

 Could you double check that what you posted compiles, and if it does,
 any idea what I'm doing wrong?

 This is with

  {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

 thanks, t.

 Prelude :r
 [1 of 1] Compiling Prompt   ( prompt.lhs, interpreted )

 prompt.lhs:140:1:
 Could not deduce (Monad tm)
   from the context (Monad (t m), MonadTrans t, MonadPrompt p m)
   arising from the superclasses of an instance declaration
   at prompt.lhs:140:1
 Possible fix:
   add (Monad tm) to the instance declaration superclass context
 In the instance declaration for `MonadPrompt p tm'

 prompt.lhs:141:13:
 Couldn't match expected type `tm' (a rigid variable)
against inferred type `t1 m1'
   `tm' is bound by the instance declaration at prompt.lhs:140:1
   Expected type: p a - tm a
   Inferred type: p a - t1 m1 a
 In the expression: lift . prompt
 In the definition of `prompt': prompt = lift . prompt
 Failed, modules loaded: none.

 This is around

  -- Just for fun, make it work with StateT as well
  -- (needs -fallow-undecidable-instances)

  instance (Monad (t m), MonadTrans t, MonadPrompt p m) = MonadPrompt p (tm) 
  where
 prompt = lift . prompt



 2007/11/18, Ryan Ingram [EMAIL PROTECTED]:
  (This message is a literate haskell file.  Code for the Prompt monad is
  preceded by ; code for my examples is preceded by ] and isn't complete,
  but intended for illustration.)
 
  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:
 
  ] type Game = IO
  ] -- or
  ] type Game = StateT GameState IO
 
  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:
 
   {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances
   #-}
   -- undecidable instances is only needed for the MonadTrans instance below
  
   module Prompt where
   import Control.Monad.Trans
   import Control.Monad.Identity
 
   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.
 
  What really made this click for me was that the prompt type could be built
  on a GADT:
 
  ] newtype GamePrompt a = GP (GameState, GameChoice a)
  ] data GameChoice a where
  ]-- pick a piece to act with
  ]ChoosePiece :: Player - GameChoice GamePiece
  ]-- pick how they should attack
  ]ChooseAttack :: Player - GamePiece - GameChoice AttackType
  ]-- etc.
 
  Now you can use this type information as part of a handler function:
  ] gameIO :: GamePrompt a - IO a
   ] gameIO (GP (state, ChoosePiece player)) = getPiece state player
  ] gameIO (GP (state, ChooseAttack player piece)) = attackMenu player piece
  ] -- ...
 
  The neat thing here is that the GADT specializes the type of IO a on the
  right hand side.  So, getPiece state player has the type IO GamePiece,
  not
  the general IO a.  So the GADT is serving as a witness of the type of
  response wanted by the game.
 
  Another neat things is that, you don't need to embed this in the IO monad at
  all; you could instead run a pure computation to do AI, or even use it for
  unit testing!
 
   -- unit testing example
   data ScriptElem p where SE :: p a - a - ScriptElem p
   type Script p = [ScriptElem p]
  
   infix 1 --
   (--) = SE
 
 
  ] gameScript :: ScriptElem GameChoice - GameChoice a - Maybe a
  ] gameScript (SE (ChoosePiece _)piece)  (ChoosePiece _)= Just piece
  ] gameScript (SE (ChooseAttack _ _) attack) (ChooseAttack _ _) = Just attack
  ] gameScript _  _
 = Nothing
  ]
 

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

2007-11-24 Thread Brent Yorgey
  -- Just for fun, make it work with StateT as well
  -- (needs -fallow-undecidable-instances)

  instance (Monad (t m), MonadTrans t, MonadPrompt p m) = MonadPrompt p
 (tm) where
 prompt = lift . prompt


Looks like that should be MonadPrompt p (t m) rather than (tm).  Note the
space.

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


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

2007-11-24 Thread Thomas Hartman
that did it, thanks.

2007/11/24, Brent Yorgey [EMAIL PROTECTED]:


 
   -- Just for fun, make it work with StateT as well
   -- (needs -fallow-undecidable-instances)
 
   instance (Monad (t m), MonadTrans t, MonadPrompt p m) = MonadPrompt p
 (tm) where
  prompt = lift . prompt
 

 Looks like that should be MonadPrompt p (t m) rather than (tm).  Note the
 space.

 -Brent


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


[Haskell-cafe] An interesting monad: Prompt

2007-11-18 Thread Ryan Ingram
(This message is a literate haskell file.  Code for the Prompt monad is
preceded by ; code for my examples is preceded by ] and isn't complete,
but intended for illustration.)

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:

] type Game = IO
] -- or
] type Game = StateT GameState IO

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:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances  #-}
 -- undecidable instances is only needed for the MonadTrans instance below

 module Prompt where
 import Control.Monad.Trans
 import Control.Monad.Identity

 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.

What really made this click for me was that the prompt type could be built
on a GADT:

] newtype GamePrompt a = GP (GameState, GameChoice a)
] data GameChoice a where
]-- pick a piece to act with
]ChoosePiece :: Player - GameChoice GamePiece
]-- pick how they should attack
]ChooseAttack :: Player - GamePiece - GameChoice AttackType
]-- etc.

Now you can use this type information as part of a handler function:
] gameIO :: GamePrompt a - IO a
] gameIO (GP (state, ChoosePiece player)) = getPiece state player
] gameIO (GP (state, ChooseAttack player piece)) = attackMenu player piece
] -- ...

The neat thing here is that the GADT specializes the type of IO a on the
right hand side.  So, getPiece state player has the type IO GamePiece,
not
the general IO a.  So the GADT is serving as a witness of the type of
response wanted by the game.

Another neat things is that, you don't need to embed this in the IO monad at
all; you could instead run a pure computation to do AI, or even use it for
unit testing!

 -- unit testing example
 data ScriptElem p where SE :: p a - a - ScriptElem p
 type Script p = [ScriptElem p]

 infix 1 --
 (--) = SE


] gameScript :: ScriptElem GameChoice - GameChoice a - Maybe a
] gameScript (SE (ChoosePiece _)piece)  (ChoosePiece _)= Just piece
] gameScript (SE (ChooseAttack _ _) attack) (ChooseAttack _ _) = Just attack
] gameScript _  _  = Nothing
]
] testGame :: Script GameChoice
] testGame =
]   [ ChoosePiece  P1-- Knight
]   , ChooseAttack P1 Knight -- Charge
]   , ChoosePiece  P2-- FootSoldier
]   , ...
]   ]

So, how to implement all of this?

 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

This doesn't require GADT's; it's just using existential types, but I like
the aesthetics better this way.

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

 -- Just for fun, make it work with StateT as well
 -- (needs -fallow-undecidable-instances)
 instance (Monad (t m), MonadTrans t, MonadPrompt p m) = MonadPrompt p (t
m) where
prompt = lift . prompt

The last bit to tie it together is an observation function which allows you
to
run the game:

 runPromptM :: Monad m = (forall a. p a - m a) - Prompt p r - m r
 runPromptM _ (PromptDone r) = return r
 runPromptM f (Prompt pa c)  = f pa = runPromptM f . c

 runPrompt :: (forall a. p a - a) - Prompt p r - r
 runPrompt f p = runIdentity $ runPromptM (Identity . f) p

 runScript ::