Re: [Haskell-beginners] Chessboard Module, opinions on…

Joe Fredette jfredett at gmail.com
Wed Oct 28 02:11:26 EDT 2009


Awesome, have you cabal-ized it? If not, it's pretty simple (look up  
'cabal' on the haskellwiki). Then you can upload it to hackage to be  
toyed with.

One thing that might be a cool direction to go w/ your project (sounds  
like you intend to make a chess playing program, this is somewhat  
orthogonal to that goal) is to build a "playback" machine. For  
instance, I play chess with people by email on a fairly regular basis.  
Specifically, we submit moves to one another in semi-standard[1]  
algebraic chess notation. So I might see a game like:


1. Kb3 e5
2. d3  d6
...
n. a4->a5 e6->d7

Where the first move is White, moving his knight to B-3, then black  
moves his pawn from e7 to e5. etc.
a move followed by a * is a check, followed by two stars is a mate.  
etc. You can poke at the wiki page for ACN for the appropriate syntax.  
My suggestion is that- often times we go many days in between moves,  
and so I don't keep track (in my head) of the last few moves he made,  
which can sometimes indicate weak points/general strategies. It would  
be _really_ nice to be able to replay old board positions at will,  
given this ACN notation of the game. Might be a nice (simple) use case  
for Parsec, and I imagine that most chess engines will have something  
like that (assuming they operate on STDIN/OUT) -- even if the syntax  
may be different. This will give you the "backend" to plug it onto  
anyway.

Anywho, good luck with your project, it looks nice!

/Joe

PS, Just noticed the little function you use to display the board (and  
stuff). You may want to poke around the 2d Pretty printers on hackage,  
they may make it easier/more extensible to render the board. Also,  
`cout`? Someone's got a bit o' the ++ in 'em... :)



[1] Okay, we mostly make it up, but it's _consistently_ arbitrary...

On Oct 28, 2009, at 1:56 AM, iæfai wrote:

>
> I have just recently finished a 'ChessBoard' module that is meant to  
> represent a chess board. I could use some opinions and/or  
> suggestions on the module.
>
> To give an example of how this can be used right now, and was my  
> immediate goal, you can do this:
>
> *ChessBoard> putStr $ cout defaultBoard
> +----+----+----+----+----+----+----+----+
> | RB | NB | BB | QB | KB | BB | NB | RB |
> +----+----+----+----+----+----+----+----+
> | PB | PB | PB | PB | PB | PB | PB | PB |
> +----+----+----+----+----+----+----+----+
> |    |    |    |    |    |    |    |    |
> +----+----+----+----+----+----+----+----+
> |    |    |    |    |    |    |    |    |
> +----+----+----+----+----+----+----+----+
> |    |    |    |    |    |    |    |    |
> +----+----+----+----+----+----+----+----+
> |    |    |    |    |    |    |    |    |
> +----+----+----+----+----+----+----+----+
> | PW | PW | PW | PW | PW | PW | PW | PW |
> +----+----+----+----+----+----+----+----+
> | RW | NW | BW | QW | KW | BW | NW | RW |
> +----+----+----+----+----+----+----+----+
>
> I have not determined exactly how I will be making moves, but the  
> logic will not be in my program. I am going to be using a chess  
> engine in another process (I haven't chosen a chess engine yet that  
> works on both windows and mac through stdin/stdout).
>
> The module itself follows, I appreciate any thoughts you might have.
>
>
> module ChessBoard where
>
> import Data.Sequence
> import Data.Foldable
> import Data.Maybe
> import Data.List as List
>
> class NiceLook a where
>    cout :: a -> String
>
>
> data Piece = Bishop | Rook | Knight | King | Queen | Pawn | NoPiece
>    deriving (Show, Eq)
>
> instance NiceLook Piece where
>        cout Bishop = "B"
>        cout Rook   = "R"
>        cout Knight = "N"
>        cout Queen  = "Q"
>        cout Pawn   = "P"
>        cout King   = "K"
>        cout _      = " "
>
> data Colour = Black | White | NoColour
>    deriving (Show, Eq)
>
> instance NiceLook Colour where
>        cout Black = "B"
>        cout White = "W"
>        cout NoColour = " "
>
>        -- error "..." might be useful
>
> data Square = Square Piece Colour
>    deriving (Show, Eq)
>
> instance NiceLook (Square) where
>        cout (Square p c) = (cout p) ++ (cout c)
>
> data Row = Row (Seq Square)
>    deriving (Show, Eq)
>
> instance NiceLook (Row) where
>        cout (Row s) = "|" ++ foldMap (\x -> " " ++ cout x ++ " |")  
> s       -- thnx Saizan
>
> makeRow n = case (List.length n) of
>                8 -> Row (fromList n)
>                _ -> error "Row is not 8 squares"
>
> makeColouredSquares n c = makeRow $ map makeSquare (zip n (replicate  
> 8 c))
>
> makeSquare (n,c) = Square n c
>
> pawns = [Pawn, Pawn, Pawn, Pawn, Pawn, Pawn, Pawn, Pawn]
> back = [Rook, Knight, Bishop, Queen, King, Bishop, Knight, Rook]
> blank = [NoPiece, NoPiece, NoPiece, NoPiece, NoPiece, NoPiece,  
> NoPiece, NoPiece]
>
> data Board = Board (Seq Row)
>    deriving (Show, Eq)
>
> instance NiceLook (Board) where
>    cout (Board c) = borderOutput ++ "\n" ++ (foldMap (\x -> cout x + 
> + "\n" ++ borderOutput ++ "\n") c)
>
> defaultBoard = Board (makeColouredSquares back Black <|
>                      makeColouredSquares pawns Black <|
>                      makeColouredSquares blank NoColour <|
>                      makeColouredSquares blank NoColour <|
>                      makeColouredSquares blank NoColour <|
>                      makeColouredSquares blank NoColour <|
>                      makeColouredSquares pawns White <|
>                      makeColouredSquares back White <| empty)
>
>
> borderOutput = "+" ++ (List.foldr1 (++) $ replicate 8 "----+")
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



More information about the Beginners mailing list