
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 "----+")

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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

If I may be so bold, this project is much more interesting than you might suspect. This is of course only the first part, but the next step is to have an opengl display (I hope to get something running on mac and windows) going and it must support opengl 1.4 due to some limitations I have. The chess AI process is something I still have to hunt for mind you, but the part that is the most interesting is that I am going to be controlling a $50,000 robot with this in class :P. This robot is a CRS-3000 I believe, it looks something like this: http://www.phym.sdu.edu.cn/rolf/image/arm_overview.jpg and it is picking up real chess pieces at the direction of the user on screen. The communication with the robot is going to be over the serial port. An interesting problem related to this is communication, luckily I have tested a serial port library that does work on windows with ghc. I will probably implement a program on the robot's 486 controller to instruct the robot on what to do specifically. My next step that could definitely use some direction would be the display part. I am limited to using power of 2 textures due to some unfortunate limitations on the machines I have available. I am thinking about this from a layered display approach. So I would be able to have a layer that would be the chess board with some interaction. Another layer would help calibrate the robot positions (luckily I am using only 4 and interpolating the rest - I figured out how to do that with some effort on Friday). I would probably start using glut for this, and hack together something, but I would imagine what I am speaking of would benefit very much from some of what haskell can do. There might even be a library that already exists that I might not have found yet. - iæfai On 2009-10-28, at 2:11 AM, Joe Fredette wrote:
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Holy. Crap. Awesome... I don't even know what to say, a $50k chess playing robot? Awesome... On Oct 28, 2009, at 2:33 AM, iæfai wrote:
If I may be so bold, this project is much more interesting than you might suspect.
This is of course only the first part, but the next step is to have an opengl display (I hope to get something running on mac and windows) going and it must support opengl 1.4 due to some limitations I have.
The chess AI process is something I still have to hunt for mind you, but the part that is the most interesting is that I am going to be controlling a $50,000 robot with this in class :P.
This robot is a CRS-3000 I believe, it looks something like this: http://www.phym.sdu.edu.cn/rolf/image/arm_overview.jpg and it is picking up real chess pieces at the direction of the user on screen. The communication with the robot is going to be over the serial port.
An interesting problem related to this is communication, luckily I have tested a serial port library that does work on windows with ghc. I will probably implement a program on the robot's 486 controller to instruct the robot on what to do specifically.
My next step that could definitely use some direction would be the display part. I am limited to using power of 2 textures due to some unfortunate limitations on the machines I have available. I am thinking about this from a layered display approach. So I would be able to have a layer that would be the chess board with some interaction. Another layer would help calibrate the robot positions (luckily I am using only 4 and interpolating the rest - I figured out how to do that with some effort on Friday).
I would probably start using glut for this, and hack together something, but I would imagine what I am speaking of would benefit very much from some of what haskell can do. There might even be a library that already exists that I might not have found yet.
- iæfai
On 2009-10-28, at 2:11 AM, Joe Fredette wrote:
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Nitpicking, a white knight cannot move to b3 on its first move. Kb3 denotes King to b3 which is not a possible first move. Nb3 is the correct notation for Knight to b3. Possible first moves for a white knight are Na3 Nc3 Nf3 and Nh3. Players in chess tournaments are required to notate their games using algebraic notation and also as a result of training/reading, the notation rolls off one's tongue. Joe Fredette wrote:
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Tony Morris http://tmorris.net/

Poor typo on my part... Though the `K` bit is just a quirk of my nonstandard notation, `G` is the symbol for king in my notation. It's just how it's always been for me, not sure why I never picked up the proper symbology... But yes, one should use _correct_ notation in a parser... :) On Oct 28, 2009, at 4:00 AM, Tony Morris wrote:
Nitpicking, a white knight cannot move to b3 on its first move. Kb3 denotes King to b3 which is not a possible first move. Nb3 is the correct notation for Knight to b3. Possible first moves for a white knight are Na3 Nc3 Nf3 and Nh3.
Players in chess tournaments are required to notate their games using algebraic notation and also as a result of training/reading, the notation rolls off one's tongue.
Joe Fredette wrote:
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Tony Morris http://tmorris.net/

Just a note to let you know: it's virtually impossible to use a
linked-list-of-linked-list or two-dimensional-array board representation as
the basis of a serious AI. It's just too inefficient (see
http://www.cis.uab.edu/hyatt/boardrep.html for some other options).
That said, if you want to use this as the basis of being able to play
through games or something, it's great.
On Wed, Oct 28, 2009 at 2:11 AM, Joe Fredette
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I am not making an AI, I am using an existing AI, so how I store it internally will not be of consequence to it. - iæfai On 2009-10-28, at 8:00 AM, Andrew Wagner wrote:
Just a note to let you know: it's virtually impossible to use a linked-list-of-linked-list or two-dimensional-array board representation as the basis of a serious AI. It's just too inefficient (see http://www.cis.uab.edu/hyatt/boardrep.html for some other options).
That said, if you want to use this as the basis of being able to play through games or something, it's great.
On Wed, Oct 28, 2009 at 2:11 AM, Joe Fredette
wrote: 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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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 "----+")
Hi iæfai! This is great! Very nicely done! I was just wondering - I potter around with crosstab code in several programming languages, and this (the table-creation code in particular) could be quite handy in that area. So, would you mind if I used this? I'll give credit of course! Many thanks for posting this neat bit of code! - Andy

You may want to look at the tabular package for table-creation code: http://hackage.haskell.org/package/tabular C. Andy Elvey schrieb:
Hi iæfai! This is great! Very nicely done! I was just wondering - I potter around with crosstab code in several programming languages, and this (the table-creation code in particular) could be quite handy in that area. So, would you mind if I used this? I'll give credit of course! Many thanks for posting this neat bit of code! - Andy

Hi Christian - Thanks for that! I'll check that out.... :) Bye for now - - Andy Christian Maeder wrote:
You may want to look at the tabular package for table-creation code: http://hackage.haskell.org/package/tabular
C.
Andy Elvey schrieb:
Hi iæfai! This is great! Very nicely done! I was just wondering - I potter around with crosstab code in several programming languages, and this (the table-creation code in particular) could be quite handy in that area. So, would you mind if I used this? I'll give credit of course! Many thanks for posting this neat bit of code! - Andy

Andy, feel free. I should note that I am going to update this code to use Text.PrettyPrint.HughesPJ shortly. In addition, it will be cabalizing it and go up on hackage once I figure it out. I will keep you informed of this. - iæfai On 2009-10-28, at 4:23 AM, Andy Elvey wrote:
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 "----+")
Hi iæfai! This is great! Very nicely done! I was just wondering - I potter around with crosstab code in several programming languages, and this (the table-creation code in particular) could be quite handy in that area. So, would you mind if I used this? I'll give credit of course! Many thanks for posting this neat bit of code! - Andy
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Great! Many thanks.... :) - Andy iæfai wrote:
Andy, feel free. I should note that I am going to update this code to use Text.PrettyPrint.HughesPJ shortly. In addition, it will be cabalizing it and go up on hackage once I figure it out.
I will keep you informed of this.
- iæfai
On 2009-10-28, at 4:23 AM, Andy Elvey wrote:
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 "----+")
Hi iæfai! This is great! Very nicely done! I was just wondering - I potter around with crosstab code in several programming languages, and this (the table-creation code in particular) could be quite handy in that area. So, would you mind if I used this? I'll give credit of course! Many thanks for posting this neat bit of code! - Andy
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

iæfai schrieb:
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 | +----+----+----+----+----+----+----+----+
nice!
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)
I'd omit NoPiece and NoColour in Piece and Colour and add an "Empty" to Square! "cout" (of "nice") for Piece and Colour could then be simply "take 1 . show", if you change Knight to Nknight. nice s = case s of Square p c -> take 1 (show p) ++ take 1 (show c) Empty -> " " Maybe an extra class NiceLook is not even necessary. Cheers Christian
participants (6)
-
Andrew Wagner
-
Andy Elvey
-
Christian Maeder
-
iæfai
-
Joe Fredette
-
Tony Morris