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