[Haskell-beginners] idiomatic haskell question

Tom Doris tomdoris at gmail.com
Mon Sep 7 13:28:22 EDT 2009


Hi all, I've recently started using Haskell and am looking for some feedback
on code I've written; I sometimes feel that maybe I'm not doing things the
best way possible that Haskell allows, and maybe missing out on obvious
improvements in brevity or elegance. So here's a tic-tac-toe solver I wrote
that does basic min-max search of the entire tree (not efficient
algorithmically, but it's tictactoe so a blank board can be fully solved in
a few seconds). Also, if people have suggestions on how to change the
program to actually output the moves it would make, please let me know -
right now it just responds with 1 for a win for X, 0 for a draw, and -1 for
a win for O. And there are probably bugs!
Thanks in advance

import Data.List
data Box = Blank | X | O deriving (Eq, Show)
-- usage: call score with the board rows concatenated: score [Blank, Blank,
Blank, Blank, Blank, Blank, Blank, Blank, Blank]
--  or      score [Blank, X, O, Blank, X, O, Blank, Blank, Blank]
-- score is 1 if X wins, 0 for draw, -1 for lose

score :: [Box] -> Int
score g  | haveline X g = 1
         | haveline O g = -1
         | gridfull g = 0
         | isxmove g = maximum (map score (makeallmoves X g))
         | otherwise = minimum (map score (makeallmoves O g))

tolines :: [Box] -> [[Box]]
tolines [a1, a2, a3, b1, b2, b3, c1, c2, c3] = [ [a1,a2,a3], [b1,b2,b3],
[c1,c2,c3],
                                              [a1,b1,c1], [a2,b2,c2],
[a3,b3,c3],
                                              [a1,b2,c3], [a3,b2,c1] ]

haveline ::  Box->[Box] -> Bool
haveline b g = any ([b,b,b]==) (tolines g)

gridfull :: [Box] -> Bool
gridfull g = not $ any  (Blank==) g

isxmove :: [Box] -> Bool
isxmove g = let movecount =  sum $ map (\b -> if b==Blank then 0 else 1) g
            in mod movecount 2 == 0

isomove = not . isxmove

fl :: Box->[Box]->[Box]->[[Box]]
fl b xs (Blank:ys) = [xs ++ b:ys]
fl _ _ _ = []

makeallmoves :: Box->[Box]-> [[Box]]
makeallmoves b g = concat $ zipWith (fl b) (inits g) (tails g)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090907/9a7ec5f1/attachment.html


More information about the Beginners mailing list