
Hi haskell helpers, Learning haskell, I wanted to explore how to write pure code and then add some IO on top of it, keeping the main code pure. The idea was to write a very simple two-player game, then define some strategies to play it that do not involve IO, and finally use strategies involving Random or IO ("ask the user"). I failed to reuse the pure code, and the only solution I found was to rewrite most things for IO. Here is my attempt in literate haskell, it is quite short, I hope someone will be kind enough to tell me what I have missed... Thanks for any answer! The game is: each player in turn chooses a number, and wins if this number has already been chosen twice (the third occurrence wins).
import Debug.Trace import Control.Monad
Choosing a number is a "move", a game is all moves played so far.
type Move = Int type Game = [Move]
newGame :: Game newGame = []
Game updating rule, Nothing for a winning move (the game stops) else Just the ongoing game.
update :: Game -> Move -> Maybe Game update game move = if move `wins` game then Nothing else Just (move:game) where move `wins` game = length (filter (== move) game) == 2
Let's give a name to both players, mainly for tracing purposes.
data Player = Player1 | Player2 deriving Show
myTrace :: Player -> Move -> (a -> a) myTrace player move = trace ((show player) ++ " plays " ++ (show move))
A strategy looks at the game and proposes the next move, and may involve state.
class Strategy a where proposeNext :: Game -> a -> (Move, a)
The "game engine" takes two strategies and returns the winner, tracing what is going on. runGame starts from a new (empty) game, runGame' updates an ongoing game and keeps track of who is Player1 or Player2.
runGame :: (Strategy a1, Strategy a2) => a1 -> a2 -> Player runGame x y = runGame' (Player1, x) (Player2, y) newGame
runGame' :: (Strategy a1, Strategy a2) => (Player, a1) -> (Player, a2) -> Game -> Player runGame' (px, x) (py, y) game = -- x and y are strategies let (move, x') = proposeNext game x follows = case update game move of Nothing -> px -- winning move Just nextgame -> runGame' (py, y) (px, x') nextgame in myTrace px move $ follows
An example of a pure strategy that plays a fixed list of numbers, then zeroes.
data Fixed = Fixed [Move] deriving Show
instance Strategy Fixed where proposeNext game s = case s of Fixed [] -> (0, Fixed []) Fixed (x:xs) -> (x, Fixed xs)
Now you may run runGame (Fixed [1,2,3]) (Fixed [3,2,1,3]) and Player2 will win. Now I want the user to be asked for moves. This one works quite well, asking *once* the user for a list of moves.
askFixed :: String -> IO Fixed askFixed name = liftM Fixed askio where askio = putStr (name ++ ", pick a list of numbers: ") >> readLn
I could easily reuse runGame:
runGameSingleIO :: (Strategy a1, Strategy a2) => IO a1 -> IO a2 -> IO Player runGameSingleIO = liftM2 runGame
And this works: runGameSingleIO (askFixed "Joe") (askFixed "Jack") Now I want each user to be asked for moves repeatedly until there is a win. This was my first try, using an infinite list and hoping lazyness would work.
askUntil :: String -> IO Fixed askUntil name = liftM Fixed (sequence $ repeat askio) where askio = putStr (name ++ ", pick a number: ") >> readLn
However it does not work, if I evaluate: liftM2 runGame (askUntil "Joe") (askUntil "Jack") then Joe is indefinitely asked for his move... Now, I supposed that IO [Move] was maybe (when triggered) a "unitary action" returning the whole list with no lazyness, and that I would rather need to have IO attached to individual moves [IO Move], so that they could be triggered independently. Am I right, or is it still subtler? Anyway, I imagined I needed to start from
data FixedIO = FixedIO [IO Move]
And that's where I failed. I could not define any instance of Strategy that could be turned to a (IO Strategy) and reuse runGame, and use [IO Move] somewhere. I could not bring the inner IOs of [IO Move] to be syhthetised in front of IO Strategy. Was it possible? All I was able to contrive is a new definition of Strategy and runGame for the IO case. This seems very awkward. Here it is:
class StrategyIO a where proposeNextIO :: Game -> a -> IO (Move, a)
runGameIO :: (StrategyIO a1, StrategyIO a2) => a1 -> a2 -> IO Player runGameIO x y = runGameIO' (Player1, x) (Player2, y) newGame
runGameIO' :: (StrategyIO a1, StrategyIO a2) => (Player, a1) -> (Player, a2) -> Game -> IO Player runGameIO' (px, x) (py, y) game = do (move, x') <- proposeNextIO game x case update game move of Nothing -> return px Just nextgame -> runGameIO' (py, y) (px, x') nextgame
Then FixedIO could be made a strategy:
instance StrategyIO FixedIO where proposeNextIO game s = case s of FixedIO [] -> return (0, FixedIO []) FixedIO (x:xs) -> liftM2 (,) x (return $ FixedIO xs)
askFixedIO :: String -> FixedIO askFixedIO name = FixedIO (repeat askio) where askio = putStr (name ++ ", pick a number: ") >> readLn
and this works: runGameIO (askFixedIO "Joe") (askFixedIO "Jack") However, I wonder how to do it reusing the "pure" versions, runGame and Strategy? Thanks for anyone that has followed so far! Eric

Hello papa, Sunday, November 29, 2009, 5:11:23 PM, you wrote:
add some IO on top of it, keeping the main code pure. The idea was to write a very simple two-player game, then define some strategies to play it that do not involve IO
ho i could do it: class Strategy state where initState :: state nextMove :: state -> (Move,state) updateState :: (Move,state) -> state where initState gives initial state, nextMove returns move and updated internal state updateState updates state with opponent's move then you can develop any IO front-end that runs two strategies each against other -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

papa.eric@free.fr escribió:
Hi haskell helpers,
Learning haskell, I wanted to explore how to write pure code and then add some IO on top of it, keeping the main code pure. The idea was to write a very simple two-player game, then define some strategies to play it that do not involve IO, and finally use strategies involving Random or IO ("ask the user"). I failed to reuse the pure code, and the only solution I found was to rewrite most things for IO. Here is my attempt in literate haskell, it is quite short, I hope someone will be kind enough to tell me what I have missed... Thanks for any answer! I know mainly two options, the first is using unsafe IO which is a small heresy.
The other is using the Control.Monad lift function which will apply pure functions over IO ones returning an IOized type. Ie if we have an b :: IO Int b = return 3 and we do c = lift (+ 2) b We will get IO(5) when we use c

There's a nice approach to this problem which is described and implemented in the MonadPrompt package[1].
Thanks a lot for this link. The "guessing game" example linked to from the documentation is still very hard to understand (I'm still struggling with monads), but it seems to fill my needs. Still more importantly to me, I understand that anyhow if I intend to use IO or random numbers, I must design my strategy from the beginning as "encapsulated in a monad". Something like: class (Monad m) => Strategy m a where ... Cheers, Eric

Eric Dedieu escribió:
Still more importantly to me, I understand that anyhow if I intend to use IO or random numbers, I must design my strategy from the beginning as "encapsulated in a monad". Something like:
class (Monad m) => Strategy m a where ...
That's not true at all, you can always pass this data to your strategy entry points and let haskell get it lazily, though it is not as intuitive as other aproaches, Ie. I need to get the next pick for my IA so I can use a function called get IA wich would take as arguments a random seed (or an infinite vector of random numbers using laziness ;) ) and the previous user inputs and strategy outputs. Of course this is just retarding the monadification of the function as soon or later you'll have to embed it into a IO monad to get the desired results. Anyway, making the strategies completely deterministic can also be useful when debugging.

Still more importantly to me, I understand that anyhow if I intend to use IO or random numbers, I must design my strategy from the beginning as "encapsulated in a monad". Something like:
class (Monad m) => Strategy m a where ...
That's not true at all, you can always pass this data to your strategy entry points and let haskell get it lazily, though it is not as intuitive as other aproaches,
That seems exactly what I had tried to do (and failed) in my original code. The Fixed type was to provide the list of moves:
data Fixed = Fixed [Move] deriving Show
and instanciate a strategy that ignores the game to make decisions, just return the provided moves, then zeroes if ever exhausted:
instance Strategy Fixed where proposeNext game s = case s of Fixed [] -> (0, Fixed []) Fixed (x:xs) -> (x, Fixed xs)
but when using an IO Fixed, the questions were not repeated lazily as needed, as if the list of moves was entirely evaluated; so this failed:
askUntil :: String -> IO Fixed askUntil name = liftM Fixed (sequence $ repeat askio) where askio = putStr (name ++ ", pick a number: ") >> readLn
I thought that sequencing [IO Move] to IO [Move] was what breaked lazyness, so I tried other ways to turn an [IO Move] into a IO Strategy, and failed. If I did not interpret correctly why this was not lazy, or if it is indeed possible to do otherwise can you please show me how? Thanks, Eric

One time I needed to do use a random number in some places of a completly
pure program so I made a infinite list of random numbers and passed it
around all the time in the functions as they where called, using the head of
the list I passed to the function whenever I needed a random number and
returning a tuple which it's second element was the tail of the random
numbers list e.g.
f:: [int] -> (a,[Int])
f randomList =
let usedRandomNumber = g $ head randomList
in (usedRandomNumber,(tail randomList))
or even something like:
f:: [int] -> (a,[Int])
f randomList =
let (usedRandomNumber,newRandomList) = g randomList
in (usedRandomNumber,newRandomList)
where g:: [int] -> (a,[Int])
The actuall code for doing this is: (Warning, it uses unsafePerformIO, just
for the seed of the random Generator, I really don't think it would do any
harm)
rand :: (RandomGen g, Random a) => (a,a) -> g -> [a]
rand range gen = as
where (a,b) = split gen -- create two separate generators
as = randomRs range a -- one infinite list of randoms
seed :: Int
seed = fromInteger (unsafePerformIO getCPUTime)
mygen = mkStdGen seed
infinito:: (Num t,Random t) => [t]
infinito = [ x | x <- rand (1,1000000) mygen]
infinito is the function that you need to call in your code that will give
you the infinite list of random numbers which will be evaluated lazyly...
Hope you can use this...
About the prompt thing, that you'll have to wait for another answer or use
what they have already told you,
Greetings,
Hector Guilarte
On Mon, Nov 30, 2009 at 8:13 PM, Eric Dedieu
Still more importantly to me, I understand that anyhow if I intend to use IO or random numbers, I must design my strategy from the beginning as "encapsulated in a monad". Something like:
class (Monad m) => Strategy m a where ...
That's not true at all, you can always pass this data to your strategy entry points and let haskell get it lazily, though it is not as intuitive as other aproaches,
That seems exactly what I had tried to do (and failed) in my original code.
The Fixed type was to provide the list of moves:
data Fixed = Fixed [Move] deriving Show
and instanciate a strategy that ignores the game to make decisions, just return the provided moves, then zeroes if ever exhausted:
instance Strategy Fixed where proposeNext game s = case s of Fixed [] -> (0, Fixed []) Fixed (x:xs) -> (x, Fixed xs)
but when using an IO Fixed, the questions were not repeated lazily as needed, as if the list of moves was entirely evaluated; so this failed:
askUntil :: String -> IO Fixed askUntil name = liftM Fixed (sequence $ repeat askio) where askio = putStr (name ++ ", pick a number: ") >> readLn
I thought that sequencing [IO Move] to IO [Move] was what breaked lazyness, so I tried other ways to turn an [IO Move] into a IO Strategy, and failed.
If I did not interpret correctly why this was not lazy, or if it is indeed possible to do otherwise can you please show me how?
Thanks, Eric _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Nov 30, 2009 at 8:36 PM, Hector Guilarte
One time I needed to do use a random number in some places of a completly pure program so I made a infinite list of random numbers and passed it around all the time in the functions as they where called, using the head of the list I passed to the function whenever I needed a random number and returning a tuple which it's second element was the tail of the random numbers list e.g.
f:: [int] -> (a,[Int]) f randomList = let usedRandomNumber = g $ head randomList in (usedRandomNumber,(tail randomList))
or even something like: f:: [int] -> (a,[Int]) f randomList = let (usedRandomNumber,newRandomList) = g randomList in (usedRandomNumber,newRandomList)
This pattern can be encapsulated in a monad: newtype RandM a = RandM { unRandM :: [Int] -> (a,[Int]) } instance Monad RandM where return x = RandM $ \randomList -> (x, randomList) m >>= g = RandM $ \randomList -> let (x, newRandomList) = unRandM m randomList in unRandM (g x) newRandomList getRandom :: RandM Int getRandom = RandM $ \(randomNumber:randomList) -> (randomNumber, randomList) See the similarity? Of course, there is no need to implement this yourself. It is already implemented as State [Int]. And as long as you are doing that, you might as well use Rand from the MonadRandom package. In fact, I have argued that you should use MonadRandom instead of the lower-level System.Random whenever possible: http://lukepalmer.wordpress.com/2009/01/17/use-monadrandom/ Luke

Luke Palmer wrote:
Hector Guilarte
wrote: f:: [int] -> (a,[Int]) f randomList = let (usedRandomNumber,newRandomList) = g randomList in (usedRandomNumber,newRandomList)
This pattern can be encapsulated in a monad:
newtype RandM a = RandM { unRandM :: [Int] -> (a,[Int]) }
instance Monad RandM where [...]
See the similarity?
Of course, there is no need to implement this yourself. It is already implemented as State [Int]. And as long as you are doing that, you might as well use Rand from the MonadRandom package. In fact, I have argued that you should use MonadRandom instead of the lower-level System.Random whenever possible: http://lukepalmer.wordpress.com/2009/01/17/use-monadrandom/
The rationale being that RandM a has a natural interpretation as "random variable of type a" with no reference to how it's actually implemented. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Sun, Nov 29, 2009 at 03:11:23PM +0100, papa.eric@free.fr wrote:
However, I wonder how to do it reusing the "pure" versions, runGame and Strategy?
There's a nice approach to this problem which is described and implemented in the MonadPrompt package[1]. Basically you have prompt :: MonadPrompt p m => p a -> m a which allows you to interact with the outside world. The beauty here is that the interection is generic, you may write a pure simulator (like yours), an IO-heavy game (like what you're trying) and possibly more, like unit tests and property checks. Cheers, [1] http://hackage.haskell.org/package/MonadPrompt -- Felipe.
participants (8)
-
Bulat Ziganshin
-
Eric Dedieu
-
Felipe Lessa
-
Hector Guilarte
-
Heinrich Apfelmus
-
klondike
-
Luke Palmer
-
papa.eric@free.fr