[Haskell-beginners] idiomatic haskell question

Andrew Wagner wagner.andrew at gmail.com
Mon Sep 7 19:44:03 EDT 2009


First of all, I highly recommend reading John Hughes' paper "Why Functional
Programming Matters" (http://www.cs.chalmers.se/~rjmh/Papers/whyfp.pdf) to
get a grasp of how to write alpha-beta and similar algorithms functionally.
Secondly, I've been playing around lately with representing tree traversals
as operations on a zipper. That is:

type TreeTraversal a = State (TreeLoc a)

This would allow you to cleanly write a traversal function which would
"return" a score, but also have, as its state, a focus on the node which it
has selected, from which you could easily get a path. See some of the top
results at http://www.google.com/search?q=haskell+zipper for a refresher on
zippers if needed. I hope to release a library around this code some day
soon.

On Mon, Sep 7, 2009 at 1:28 PM, Tom Doris <tomdoris at gmail.com> wrote:

> 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)
>
>
>
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090907/7be5e917/attachment-0001.html


More information about the Beginners mailing list