Giter Club home page Giter Club logo

chessio's Introduction

A Haskell chess library and console UCI frontend program

Build status

chessIO is a Haskell library for working with chess positions and moves, and a console frontend program (cboard) to work with UCI compatible chess engines.

The Library

The main module provided by the library is Game.Chess, which defines data types and functions for working with chess positions and moves. It offers a fully compliant move generator and parsing for and printing positions in Forsyth-Edwards Notation and moves in Algebraic Notation.

Module Game.Chess.UCI provides functionality to run an external process which understands the Universal Chess Interface protocol from within Haskell.

Console frontend for the Universal Chess Interface protocl

cboard is a simple console (text-mode) frontend for interacting with chess engines (like stockfish or glaurung) which make use of the UCI protocol.

To launch a chess engine, simply pass its executable name and arguments to cboard. For instance, cboard stockfish.

chessio's People

Contributors

mlang avatar peterbecich avatar phadej avatar tochicool avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar

chessio's Issues

half-move counter seems to be broken.

Thanks for this awesome library!

I think I found a small bug in move application, the half move counter doesn't seem to reset after pawn moves:

*Game.Chess> doPly startpos (move D2 D4)
"rnbqkbnr/pppppppp/8/8/3P4/8/PPP1PPPP/RNBQKBNR b KQkq d3 1 1"

It should be

"rnbqkbnr/pppppppp/8/8/3P4/8/PPP1PPPP/RNBQKBNR b KQkq d3 0 1"

(FWIW, lichess forget to mark enpassant square, though according to wikipedia

En passant target square in algebraic notation. If there's no en passant target square, this is "-". If a pawn has just made a two-square move, this is the position "behind" the pawn. This is recorded regardless of whether there is a pawn in position to make an en passant capture.

chess.com analysis includes d3).

EDIT: the counter doesn't seem to reset after captures either.

Add stripBOM to readPGNFile

diff --git a/chessIO-0.7.0.0/src/Game/Chess/PGN.hs b/chessIO-0.7.0.0/src/Game/Chess/PGN.hs
index f8faf3f..fa7ea2e 100644
--- a/chessIO-0.7.0.0/src/Game/Chess/PGN.hs
+++ b/chessIO-0.7.0.0/src/Game/Chess/PGN.hs
@@ -93,7 +93,13 @@ data PlyData = PlyData {
 } deriving (Eq, Show)
 
 readPGNFile :: MonadIO m => FilePath -> m (Either String PGN)
-readPGNFile fp = liftIO $ first errorBundlePretty . parse pgn fp <$> BS.readFile fp
+readPGNFile fp = liftIO $ first errorBundlePretty . parse pgn fp . stripBOM <$> BS.readFile fp
+
+stripBOM :: ByteString -> ByteString
+stripBOM bs
+    | BS.take 3 bs == "\xEF\xBB\xBF" = BS.drop 3 bs
+    | otherwise                      = bs
+
 
 hPutPGN :: Handle -> RAVOrder (Doc ann) -> PGN -> IO ()
 hPutPGN h ro (PGN games) = for_ games $ \g -> do

Some windows software persistently adds the BOM. The stripping function could be smarter (e.g. recognize other UTF encodings via BOM if present) but I haven't seen such PGN files in the wild.

bug in toFEN, castling mask is not cleared when kings move

>>> foldl doPly startpos [move E2 E4, move E7 E5, move E1 E2, move E8 E7]
"rnbq1bnr/ppppkppp/8/4p3/4P3/8/PPPPKPPP/RNBQ1BNR w  - 4 3"

Note: no - for castling rights. This is because

showHex (flags $ foldl doPly startpos [move E2 E4, move E7 E5, move E1 E2, move E8 E7]) ""
"8100000000000081"

(rook) flags are still there.

The toFEN does

  , showCst (flags `clearMask` epMask)
 ... 
 showEP 0 = "-"

But that is incorrect, as there are "rooks" in the flags bitboard, they haven't moved so their bits are still up.

Make total version of doPly

It would've been great if library exported a total version of doPly :: Position -> Ply -> Position which returns Maybe Position.

Make newtype Sq = Sq Int, use less raw Int

... introduce newtype Rank and newtype File.

I made such change in my own (private) fork, adding a module

module Game.Chess.Square (
    Rank (Rank1,Rank2,Rank3,Rank4,Rank5,Rank6,Rank7,Rank8),mkRank,unRank,
    File (FileA,FileB,FileC,FileD,FileE,FileF,FileG,FileH),mkFile,unFile,
    Sq (A1,A2,A3,A4,A5,A6,A7,A8
       ,B1,B2,B3,B4,B5,B6,B7,B8
       ,C1,C2,C3,C4,C5,C6,C7,C8
       ,D1,D2,D3,D4,D5,D6,D7,D8
       ,E1,E2,E3,E4,E5,E6,E7,E8
       ,F1,F2,F3,F4,F5,F6,F7,F8
       ,G1,G2,G3,G4,G5,G6,G7,G8
       ,H1,H2,H3,H4,H5,H6,H7,H8)
       , mkSq, unSq,
    isDark, isLight,
    IsSquare (..), toCoord, toRF, toIndex,
) where

import Game.Chess.Internal.Prelude

import Data.Char (ord, chr)
import GHC.Stack
import Data.Ix (Ix (..))

-------------------------------------------------------------------------------
-- Rank
-------------------------------------------------------------------------------

newtype Rank = Rank Int
  deriving (Eq, Ord)

unRank :: Rank -> Int
unRank = coerce

-- TODO: make efficient version
mkRank :: HasCallStack => Int -> Rank
mkRank n
    | n >= 0 && n <= 7 = Rank n
    | otherwise        = error $ "mkRank " ++ show n

instance Show Rank where
    showsPrec _ (Rank 0) = showString "Rank1"
    showsPrec _ (Rank 1) = showString "Rank2"
    showsPrec _ (Rank 2) = showString "Rank3"
    showsPrec _ (Rank 3) = showString "Rank4"
    showsPrec _ (Rank 4) = showString "Rank5"
    showsPrec _ (Rank 5) = showString "Rank6"
    showsPrec _ (Rank 6) = showString "Rank7"
    showsPrec _ (Rank 7) = showString "Rank8"
    showsPrec d (Rank n) = showParen (d > 10) $
        showString "Rank " . showsPrec 11 n

instance Enum Rank where
    toEnum n | n >= 0 && n <= 7 = Rank n
             | otherwise        = error $ "Rank out-of-bound " ++ show n

    fromEnum (Rank n) = n

instance Bounded Rank where
    minBound = Rank1
    maxBound = Rank8

pattern Rank1, Rank2, Rank3, Rank4, Rank5, Rank6, Rank7, Rank8 :: Rank
pattern Rank1 = Rank 0
pattern Rank2 = Rank 1
pattern Rank3 = Rank 2
pattern Rank4 = Rank 3
pattern Rank5 = Rank 4
pattern Rank6 = Rank 5
pattern Rank7 = Rank 6
pattern Rank8 = Rank 7

{-# COMPLETE Rank1, Rank2, Rank3, Rank4, Rank5, Rank6, Rank7, Rank8 :: Rank #-}

-------------------------------------------------------------------------------
-- File
-------------------------------------------------------------------------------

newtype File = File Int
  deriving (Eq, Ord)

unFile :: File -> Int
unFile = coerce

mkFile :: HasCallStack => Int -> File
mkFile n
    | n >= 0 && n <= 7 = File n
    | otherwise        = error $ "mkFile " ++ show n

instance Show File where
    showsPrec _ (File 0) = showString "FileA"
    showsPrec _ (File 1) = showString "FileB"
    showsPrec _ (File 2) = showString "FileC"
    showsPrec _ (File 3) = showString "FileD"
    showsPrec _ (File 4) = showString "FileE"
    showsPrec _ (File 5) = showString "FileF"
    showsPrec _ (File 6) = showString "FileG"
    showsPrec _ (File 7) = showString "FileH"
    showsPrec d (File n) = showParen (d > 10) $
        showString "File " . showsPrec 11 n

instance Enum File where
    toEnum n | n >= 0 && n <= 7 = File n
             | otherwise        = error $ "File out-of-bound " ++ show n

    fromEnum (File n) = n

instance Bounded File where
    minBound = FileA
    maxBound = FileH


pattern FileA, FileB, FileC, FileD, FileE, FileF, FileG, FileH :: File
pattern FileA = File 0
pattern FileB = File 1
pattern FileC = File 2
pattern FileD = File 3
pattern FileE = File 4
pattern FileF = File 5
pattern FileG = File 6
pattern FileH = File 7

{-# COMPLETE FileA, FileB, FileC, FileD, FileE, FileF, FileG, FileH :: File #-}

-------------------------------------------------------------------------------
-- Square
-------------------------------------------------------------------------------

newtype Sq = Sq Int
  deriving (Eq, Ord)

instance Ix Sq where
    range (Sq i, Sq j) = [Sq k | k <- [i..j]]
    index (Sq i, Sq j) (Sq k) = index (i, j) k
    inRange (Sq i, Sq j) (Sq k) = inRange (i, j) k

    rangeSize (Sq i, Sq j) = j - i

unSq :: Sq -> Int
unSq = coerce

-- TODO: this check is expensive, maybe only worth in "debug" builds.
mkSq :: HasCallStack => Int -> Sq
mkSq n
    | n >= 0 && n <= 63 = Sq n
    | otherwise         = error $ "mkSq " ++ show n

instance Show Sq where
    showsPrec d (Sq i)
        | i >= 0 && i <= 63 = showString [f', r']
        | otherwise         = showParen (d > 10) $
            showString "Sq " . showsPrec 11 i
      where
        (r, f) = i `divMod` 8
        r' = chr (r + ord '1')
        f' = chr (f + ord 'A')

instance Enum Sq where
    toEnum n | n >= 0 && n <= 63 = Sq n
             | otherwise         = error $ "Sq out-of-bound " ++ show n

    fromEnum (Sq n) = n

instance Bounded Sq where
    minBound = A1
    maxBound = H8

pattern A1, A2, A3, A4, A5, A6, A7, A8 :: Sq
pattern B1, B2, B3, B4, B5, B6, B7, B8 :: Sq
pattern C1, C2, C3, C4, C5, C6, C7, C8 :: Sq
pattern D1, D2, D3, D4, D5, D6, D7, D8 :: Sq
pattern E1, E2, E3, E4, E5, E6, E7, E8 :: Sq
pattern F1, F2, F3, F4, F5, F6, F7, F8 :: Sq
pattern G1, G2, G3, G4, G5, G6, G7, G8 :: Sq
pattern H1, H2, H3, H4, H5, H6, H7, H8 :: Sq

pattern A1 = Sq 0
pattern B1 = Sq 1
pattern C1 = Sq 2
pattern D1 = Sq 3
pattern E1 = Sq 4
pattern F1 = Sq 5
pattern G1 = Sq 6
pattern H1 = Sq 7

pattern A2 = Sq 8
pattern B2 = Sq 9
pattern C2 = Sq 10
pattern D2 = Sq 11
pattern E2 = Sq 12
pattern F2 = Sq 13
pattern G2 = Sq 14
pattern H2 = Sq 15

pattern A3 = Sq 16
pattern B3 = Sq 17
pattern C3 = Sq 18
pattern D3 = Sq 19
pattern E3 = Sq 20
pattern F3 = Sq 21
pattern G3 = Sq 22
pattern H3 = Sq 23

pattern A4 = Sq 24
pattern B4 = Sq 25
pattern C4 = Sq 26
pattern D4 = Sq 27
pattern E4 = Sq 28
pattern F4 = Sq 29
pattern G4 = Sq 30
pattern H4 = Sq 31

pattern A5 = Sq 32
pattern B5 = Sq 33
pattern C5 = Sq 34
pattern D5 = Sq 35
pattern E5 = Sq 36
pattern F5 = Sq 37
pattern G5 = Sq 38
pattern H5 = Sq 39

pattern A6 = Sq 40
pattern B6 = Sq 41
pattern C6 = Sq 42
pattern D6 = Sq 43
pattern E6 = Sq 44
pattern F6 = Sq 45
pattern G6 = Sq 46
pattern H6 = Sq 47

pattern A7 = Sq 48
pattern B7 = Sq 49
pattern C7 = Sq 50
pattern D7 = Sq 51
pattern E7 = Sq 52
pattern F7 = Sq 53
pattern G7 = Sq 54
pattern H7 = Sq 55

pattern A8 = Sq 56
pattern B8 = Sq 57
pattern C8 = Sq 58
pattern D8 = Sq 59
pattern E8 = Sq 60
pattern F8 = Sq 61
pattern G8 = Sq 62
pattern H8 = Sq 63

-------------------------------------------------------------------------------
-- IsSquare
-------------------------------------------------------------------------------

class IsSquare sq where
    toSq   :: sq -> Sq
    fromSq :: Sq -> sq

    file :: sq -> File
    file = snd . fromSq . toSq

    rank :: sq -> Rank
    rank = fst . fromSq . toSq

instance IsSquare Sq where
    toSq   = id
    fromSq = id

instance (rank ~ Rank, file ~ File) => IsSquare (rank, file) where
    toSq (Rank r, File f) = mkSq (r*8 + f)
    fromSq (Sq i) = case i `divMod` 8 of
        (r, f) -> (Rank r, File f)

    rank = fst
    file = snd

toIndex :: forall sq. IsSquare sq => sq -> Int
toIndex = coerce (toSq :: sq -> Sq)

toRF :: forall sq. IsSquare sq => sq -> (Int, Int)
toRF (fromSq . toSq -> (Rank r, File f)) = (r, f)

isDark :: IsSquare sq => sq -> Bool
isDark sq = (0xaa55aa55aa55aa55 :: Word64) `testBit` toIndex sq

isLight :: IsSquare sq => sq -> Bool
isLight = not . isDark

toCoord :: (IsSquare sq, IsString s) => sq -> s
toCoord (toRF -> (r,f)) = fromString [chr (f + ord 'a'), chr (r + ord '1')]

and adjusting everything else to use this.

IMHO it made library API nicer.

Compilation error with GHC-8.6 and GHC-8.8

src/Game/Chess/Internal/ECO.hs:43:61: error:
    Module ‘Language.Haskell.TH.Syntax’ does not export ‘liftTyped’
   |
43 | import           Language.Haskell.TH.Syntax (Lift, Q, TExp, liftTyped)
   |                                                             ^^^^^^^^^

Add support for PGN comments

This would be a fantastic feature if implemented. Since time-stamps are typically annotated within the comment syntax, all clock-info is lost during import.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.