[Haskell-cafe] Help mixing pure and IO code

papa.eric at free.fr papa.eric at free.fr
Sun Nov 29 09:11:23 EST 2009


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


More information about the Haskell-Cafe mailing list