Difference between revisions of "TicTacToe"

From HaskellWiki
Jump to navigation Jump to search
(Used StateT to make a single instance of the board)
Line 2: Line 2:
   
 
== Diary of a Tic-tac-toe program ==
 
== Diary of a Tic-tac-toe program ==
  +
1/27/2007
 
 
<haskell>
 
<haskell>
 
module TicTacToe
 
module TicTacToe
Line 17: Line 17:
 
firstFree (x:xs) | x == ' ' = 1
 
firstFree (x:xs) | x == ' ' = 1
 
| otherwise = 1 + (firstFree xs)
 
| otherwise = 1 + (firstFree xs)
  +
 
main = do
 
main = do
 
putStrLn "Enter your move:"
 
putStrLn "Enter your move:"
Line 71: Line 72:
 
* computer vs. computer mode
 
* computer vs. computer mode
 
* genetically-evolved players
 
* genetically-evolved players
  +
  +
1/29/2007
  +
Well, the TicTacToe project is now two days old, and it's time to check in on its growth. Here's the newest snapshot of its code:
  +
  +
<haskell>
  +
module TicTacToe
  +
where
  +
  +
import Control.Monad.State
  +
  +
main = runStateT code " " >> return ()
  +
  +
code :: StateT String IO ()
  +
code = do
  +
m1 <- lift getLine
  +
modify (place (read m1) 'X')
  +
modify (makeMove)
  +
  +
m2 <- lift getLine
  +
modify (place (read m2) 'X')
  +
modify (makeMove)
  +
  +
m3 <- lift getLine
  +
modify (place (read m3) 'X')
  +
modify (makeMove)
  +
  +
m4 <- lift getLine
  +
modify (place (read m4) 'X')
  +
modify (makeMove)
  +
  +
m5 <- lift getLine
  +
modify (place (read m5) 'X')
  +
  +
y <- get
  +
liftIO $ print y
  +
return ()
  +
  +
place :: Int -> Char -> String -> String
  +
place _ _ [] = []
  +
place 1 c (x:xs) = c : xs
  +
place n c (x:xs) = x : (place (n-1) c xs)
  +
  +
findFree :: String -> Int
  +
findFree (x:xs) | x == ' ' = 1
  +
| otherwise = 1 + findFree xs
  +
  +
makeMove :: String -> String
  +
makeMove = flip place 'O' =<< findFree
  +
</haskell>
  +
  +
Well, perhaps 'growth' isn't quite the correct term, since the code has actually shrunk by several lines. Nor has it 'grown' in the features it has, yet. What has happened is that we've used the State monad to get rid of the numerous boards threaded through main. Now there's a single board (which makes good logical sense), which we can access and modify using get, put, and modify. It's still as dumb as a rock, but at least it's a little cleaner!

Revision as of 03:50, 30 January 2007


Diary of a Tic-tac-toe program

1/27/2007

module TicTacToe
where

data Board = String

place :: String -> Int -> Char -> String
place [] _ _ = []
place (x:xs) 1 c = c : xs
place (x:xs) n c = x : (place xs (n-1) c)

firstFree :: String -> Int
firstFree (x:xs) | x == ' ' = 1
                 | otherwise = 1 + (firstFree xs)

main = do
  putStrLn "Enter your move:"
  move1 <- getLine
  let move1Num = read move1
  let board1 = place "         " move1Num 'X'
  let board2 = place board1 (firstFree board1) 'O'
  putStrLn ("New board:" ++ board2)

  putStrLn "Enter your move:"
  move2 <- getLine
  let move2Num = read move2
  let board3 = place board2 move2Num 'X'
  let board4 = place board3 (firstFree board3) 'O'
  putStrLn ("New board:" ++ board4)

  putStrLn "Enter your move:"
  move3 <- getLine
  let move3Num = read move3
  let board5 = place board4 move3Num 'X'
  let board6 = place board5 (firstFree board5) 'O'
  putStrLn ("New board:" ++ board6)

  putStrLn "Enter your move:"
  move4 <- getLine
  let move4Num = read move4
  let board7 = place board6 move4Num 'X'
  let board8 = place board7 (firstFree board7) 'O'
  putStrLn ("New board:" ++ board8)

  putStrLn "Enter your move:"
  move5 <- getLine
  let move5Num = read move5
  let board9 = place board8 move5Num 'X'

  putStrLn ("Final board:" ++ board9)


Hideous, isn't it? Why, thank you! That is, in fact, the point. I want to start with an absolutely hideous piece of code, and add features, re-factoring as I go. It seems to me like there's actually a lot you can do with tic-tac-toe, and so I hope this will turn into something instructive, both for me and for anyone who wants to follow along, and/or contribute.

Feature ideas (in no particular order):

  • output a real board
  • game-end condition check
  • curses-based interface
  • tic-tac-toe variants
  • computer can be x or o
  • two-player mode
  • tournament mode
  • web interface
  • lazy alpha-beta player
  • random square player
  • brute-force player
  • computer vs. computer mode
  • genetically-evolved players

1/29/2007 Well, the TicTacToe project is now two days old, and it's time to check in on its growth. Here's the newest snapshot of its code:

module TicTacToe
where

import Control.Monad.State

main = runStateT code "         " >> return ()

code :: StateT String IO ()
code = do
  m1 <- lift getLine
  modify (place (read m1) 'X')
  modify (makeMove)

  m2 <- lift getLine
  modify (place (read m2) 'X')
  modify (makeMove)

  m3 <- lift getLine
  modify (place (read m3) 'X')
  modify (makeMove)

  m4 <- lift getLine
  modify (place (read m4) 'X')
  modify (makeMove)

  m5 <- lift getLine
  modify (place (read m5) 'X')

  y <- get
  liftIO $ print y
  return ()

place :: Int -> Char -> String -> String
place _ _ [] = []
place 1 c (x:xs) = c : xs
place n c (x:xs) = x : (place (n-1) c xs)

findFree :: String -> Int
findFree (x:xs) | x == ' ' = 1
                | otherwise = 1 + findFree xs

makeMove :: String -> String
makeMove = flip place 'O' =<< findFree

Well, perhaps 'growth' isn't quite the correct term, since the code has actually shrunk by several lines. Nor has it 'grown' in the features it has, yet. What has happened is that we've used the State monad to get rid of the numerous boards threaded through main. Now there's a single board (which makes good logical sense), which we can access and modify using get, put, and modify. It's still as dumb as a rock, but at least it's a little cleaner!