chessIO-0.9.3.1: Basic chess library
Copyright(c) Mario Lang 2021
LicenseBSD3
Maintainermlang@blind.guru
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Game.Chess.PGN

Description

A PGN file consists of a list of games. Each game consists of a tag list, the outcome, and a forest of rosetrees.

Synopsis

Documentation

newtype PGN Source #

Constructors

PGN [Game] 

Instances

Instances details
Monoid PGN Source # 
Instance details

Defined in Game.Chess.PGN

Methods

mempty :: PGN #

mappend :: PGN -> PGN -> PGN #

mconcat :: [PGN] -> PGN #

Semigroup PGN Source # 
Instance details

Defined in Game.Chess.PGN

Methods

(<>) :: PGN -> PGN -> PGN #

sconcat :: NonEmpty PGN -> PGN #

stimes :: Integral b => b -> PGN -> PGN #

Eq PGN Source # 
Instance details

Defined in Game.Chess.PGN

Methods

(==) :: PGN -> PGN -> Bool #

(/=) :: PGN -> PGN -> Bool #

Wrapped PGN Source # 
Instance details

Defined in Game.Chess.PGN

Associated Types

type Unwrapped PGN #

PGN ~ t => Rewrapped PGN t Source # 
Instance details

Defined in Game.Chess.PGN

type Unwrapped PGN Source # 
Instance details

Defined in Game.Chess.PGN

type Unwrapped PGN = [Game]

data Game Source #

Constructors

CG 

Fields

Instances

Instances details
Generic Game Source # 
Instance details

Defined in Game.Chess.PGN

Associated Types

type Rep Game :: Type -> Type #

Methods

from :: Game -> Rep Game x #

to :: Rep Game x -> Game #

Show Game Source # 
Instance details

Defined in Game.Chess.PGN

Methods

showsPrec :: Int -> Game -> ShowS #

show :: Game -> String #

showList :: [Game] -> ShowS #

Eq Game Source # 
Instance details

Defined in Game.Chess.PGN

Methods

(==) :: Game -> Game -> Bool #

(/=) :: Game -> Game -> Bool #

Hashable Game Source # 
Instance details

Defined in Game.Chess.PGN

Methods

hashWithSalt :: Int -> Game -> Int #

hash :: Game -> Int #

type Rep Game Source # 
Instance details

Defined in Game.Chess.PGN

type Rep Game = D1 ('MetaData "Game" "Game.Chess.PGN" "chessIO-0.9.3.1-FhorHdlbYNXK07vrmB8ltu" 'False) (C1 ('MetaCons "CG" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cgTags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Text, Text)]) :*: (S1 ('MetaSel ('Just "_cgForest") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Tree (Annotated Ply)]) :*: S1 ('MetaSel ('Just "_cgOutcome") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Outcome))))

data Outcome Source #

Constructors

Win Color 
Draw 
Undecided 

Instances

Instances details
Generic Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Associated Types

type Rep Outcome :: Type -> Type #

Methods

from :: Outcome -> Rep Outcome x #

to :: Rep Outcome x -> Outcome #

Show Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Eq Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Methods

(==) :: Outcome -> Outcome -> Bool #

(/=) :: Outcome -> Outcome -> Bool #

Ord Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Hashable Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Methods

hashWithSalt :: Int -> Outcome -> Int #

hash :: Outcome -> Int #

Pretty Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Methods

pretty :: Outcome -> Doc ann #

prettyList :: [Outcome] -> Doc ann #

Lift Outcome Source # 
Instance details

Defined in Game.Chess.PGN

Methods

lift :: Quote m => Outcome -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Outcome -> Code m Outcome #

type Rep Outcome Source # 
Instance details

Defined in Game.Chess.PGN

type Rep Outcome = D1 ('MetaData "Outcome" "Game.Chess.PGN" "chessIO-0.9.3.1-FhorHdlbYNXK07vrmB8ltu" 'False) (C1 ('MetaCons "Win" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)) :+: (C1 ('MetaCons "Draw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undecided" 'PrefixI 'False) (U1 :: Type -> Type)))

data Annotated a Source #

Constructors

Ann 

Fields

Instances

Instances details
Applicative Annotated Source # 
Instance details

Defined in Game.Chess.PGN

Methods

pure :: a -> Annotated a #

(<*>) :: Annotated (a -> b) -> Annotated a -> Annotated b #

liftA2 :: (a -> b -> c) -> Annotated a -> Annotated b -> Annotated c #

(*>) :: Annotated a -> Annotated b -> Annotated b #

(<*) :: Annotated a -> Annotated b -> Annotated a #

Functor Annotated Source # 
Instance details

Defined in Game.Chess.PGN

Methods

fmap :: (a -> b) -> Annotated a -> Annotated b #

(<$) :: a -> Annotated b -> Annotated a #

Generic (Annotated a) Source # 
Instance details

Defined in Game.Chess.PGN

Associated Types

type Rep (Annotated a) :: Type -> Type #

Methods

from :: Annotated a -> Rep (Annotated a) x #

to :: Rep (Annotated a) x -> Annotated a #

Show a => Show (Annotated a) Source # 
Instance details

Defined in Game.Chess.PGN

Eq a => Eq (Annotated a) Source # 
Instance details

Defined in Game.Chess.PGN

Methods

(==) :: Annotated a -> Annotated a -> Bool #

(/=) :: Annotated a -> Annotated a -> Bool #

Hashable a => Hashable (Annotated a) Source # 
Instance details

Defined in Game.Chess.PGN

Methods

hashWithSalt :: Int -> Annotated a -> Int #

hash :: Annotated a -> Int #

Lift a => Lift (Annotated a :: Type) Source # 
Instance details

Defined in Game.Chess.PGN

Methods

lift :: Quote m => Annotated a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Annotated a -> Code m (Annotated a) #

type Rep (Annotated a) Source # 
Instance details

Defined in Game.Chess.PGN

type Rep (Annotated a) = D1 ('MetaData "Annotated" "Game.Chess.PGN" "chessIO-0.9.3.1-FhorHdlbYNXK07vrmB8ltu" 'False) (C1 ('MetaCons "Ann" 'PrefixI 'True) (S1 ('MetaSel ('Just "_annPrefixNAG") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Int]) :*: (S1 ('MetaSel ('Just "_annPly") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_annSuffixNAG") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Int]))))

annPrefixNAG :: forall a. Lens' (Annotated a) [Int] Source #

annPly :: forall a a. Lens (Annotated a) (Annotated a) a a Source #

annSuffixNAG :: forall a. Lens' (Annotated a) [Int] Source #

A PGN parser

pgn :: Parser PGN Source #

Prettyprinting

hPutPGN :: Handle -> RAVOrder (Doc ann) -> PGN -> IO () Source #

pgnDoc :: RAVOrder (Doc ann) -> PGN -> Doc ann Source #

type RAVOrder a = ([Tree (Annotated Ply)] -> a) -> [Tree (Annotated Ply)] -> [a] Source #

gameDoc :: RAVOrder (Doc ann) -> Game -> Doc ann Source #