{-# LANGUAGE EmptyDataDecls #-}
module Data.SGF.Types (
Game(..), GameTree(..), GameNode(..),
Move(..), Setup(..),
Annotation(..), Markup(..), GameInfo(..), GameInfoType(..),
emptyGameNode, emptyMove, emptySetup, emptyGameInfo, emptyAnnotation, emptyMarkup,
NodeGo, MoveGo(..), RuleSetGo(..), GameInfoGo(..), AnnotationGo,
NodeBackgammon, RuleSetBackgammon(..), GameInfoBackgammon,
MatchInfo(..),
NodeLinesOfAction, GameInfoLinesOfAction(..),
InitialPosition(..), InitialPlacement(..),
NodeHex, GameInfoHex,
ViewerSetting(..),
NodeOcti, RuleSetOcti(..), GameInfoOcti(..),
MajorVariation(..), MinorVariation(..),
NodeOther,
Collection, Point,
Application, Version, AutoMarkup,
TreeGo, TreeBackgammon, TreeLinesOfAction, TreeHex, TreeOcti, TreeOther,
Color(..), RankScale(..),
Emphasis(..), Certainty(..), FuzzyBool(..),
GameType(..),
Judgment(..), Quality(..),
Mark(..), Numbering(..), VariationType(..), FigureFlag(..),
WinType(..), GameResult(..), Rank(..), RuleSet(..),
Round(..), PartialDate(..), Figure(..),
Void
) where
import Data.List
import Data.Map hiding (empty, filter, findIndex)
import Data.Maybe
import Data.Ord
import Data.Set hiding (empty, filter, findIndex)
import Data.Tree
import Data.Word
import Prelude hiding (round)
import qualified Data.Map as Map
import qualified Data.Set as Set
data Void
instance Eq Void where Void
_ == :: Void -> Void -> Bool
== Void
_ = Bool
True
instance Ord Void where compare :: Void -> Void -> Ordering
compare Void
_ Void
_ = Ordering
EQ
instance Read Void where readsPrec :: Int -> ReadS Void
readsPrec Int
_ String
_ = []
instance Show Void where show :: Void -> String
show Void
_ = String
""
data GameType =
Go | Othello | Chess | Gomoku | NineMen'sMorris |
Backgammon | ChineseChess | Shogi | LinesOfAction | Ataxx |
Hex | Jungle | Neutron | |
Quadrature | Trax | Tantrix | Amazons | Octi | Gess |
Twixt | Zertz | Plateau | Yinsh | Punct | Gobblet | Hive |
Exxit | Hnefatal | Kuba | Tripples | Chase | TumblingDown |
Sahara | Byte | Focus | Dvonn | Tamsk | Gipf | Kropki
deriving (GameType -> GameType -> Bool
(GameType -> GameType -> Bool)
-> (GameType -> GameType -> Bool) -> Eq GameType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameType -> GameType -> Bool
== :: GameType -> GameType -> Bool
$c/= :: GameType -> GameType -> Bool
/= :: GameType -> GameType -> Bool
Eq, Eq GameType
Eq GameType =>
(GameType -> GameType -> Ordering)
-> (GameType -> GameType -> Bool)
-> (GameType -> GameType -> Bool)
-> (GameType -> GameType -> Bool)
-> (GameType -> GameType -> Bool)
-> (GameType -> GameType -> GameType)
-> (GameType -> GameType -> GameType)
-> Ord GameType
GameType -> GameType -> Bool
GameType -> GameType -> Ordering
GameType -> GameType -> GameType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameType -> GameType -> Ordering
compare :: GameType -> GameType -> Ordering
$c< :: GameType -> GameType -> Bool
< :: GameType -> GameType -> Bool
$c<= :: GameType -> GameType -> Bool
<= :: GameType -> GameType -> Bool
$c> :: GameType -> GameType -> Bool
> :: GameType -> GameType -> Bool
$c>= :: GameType -> GameType -> Bool
>= :: GameType -> GameType -> Bool
$cmax :: GameType -> GameType -> GameType
max :: GameType -> GameType -> GameType
$cmin :: GameType -> GameType -> GameType
min :: GameType -> GameType -> GameType
Ord, GameType
GameType -> GameType -> Bounded GameType
forall a. a -> a -> Bounded a
$cminBound :: GameType
minBound :: GameType
$cmaxBound :: GameType
maxBound :: GameType
Bounded, Int -> GameType -> ShowS
[GameType] -> ShowS
GameType -> String
(Int -> GameType -> ShowS)
-> (GameType -> String) -> ([GameType] -> ShowS) -> Show GameType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameType -> ShowS
showsPrec :: Int -> GameType -> ShowS
$cshow :: GameType -> String
show :: GameType -> String
$cshowList :: [GameType] -> ShowS
showList :: [GameType] -> ShowS
Show, ReadPrec [GameType]
ReadPrec GameType
Int -> ReadS GameType
ReadS [GameType]
(Int -> ReadS GameType)
-> ReadS [GameType]
-> ReadPrec GameType
-> ReadPrec [GameType]
-> Read GameType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameType
readsPrec :: Int -> ReadS GameType
$creadList :: ReadS [GameType]
readList :: ReadS [GameType]
$creadPrec :: ReadPrec GameType
readPrec :: ReadPrec GameType
$creadListPrec :: ReadPrec [GameType]
readListPrec :: ReadPrec [GameType]
Read)
allGameTypesInSGFOrder :: [GameType]
allGameTypesInSGFOrder =
[GameType
Go, GameType
Othello, GameType
Chess, GameType
Gomoku, GameType
NineMen'sMorris, GameType
Backgammon,
GameType
ChineseChess, GameType
Shogi, GameType
LinesOfAction, GameType
Ataxx, GameType
Hex, GameType
Jungle,
GameType
Neutron, GameType
Philosopher'sFootball, GameType
Quadrature, GameType
Trax, GameType
Tantrix,
GameType
Amazons, GameType
Octi, GameType
Gess, GameType
Twixt, GameType
Zertz, GameType
Plateau, GameType
Yinsh, GameType
Punct,
GameType
Gobblet, GameType
Hive, GameType
Exxit, GameType
Hnefatal, GameType
Kuba, GameType
Tripples, GameType
Chase,
GameType
TumblingDown, GameType
Sahara, GameType
Byte, GameType
Focus, GameType
Dvonn, GameType
Tamsk, GameType
Gipf,
GameType
Kropki
]
instance Enum GameType where
toEnum :: Int -> GameType
toEnum Int
n = [GameType]
allGameTypesInSGFOrder [GameType] -> Int -> GameType
forall a. HasCallStack => [a] -> Int -> a
!! (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
fromEnum :: GameType -> Int
fromEnum GameType
t = (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int -> Int) -> ([GameType] -> Int) -> [GameType] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Int -> Int)
-> ([GameType] -> Maybe Int) -> [GameType] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GameType -> Bool) -> [GameType] -> Maybe Int
forall a. (a -> Bool) -> [a] -> Maybe Int
findIndex (GameType
tGameType -> GameType -> Bool
forall a. Eq a => a -> a -> Bool
==) ([GameType] -> Int) -> [GameType] -> Int
forall a b. (a -> b) -> a -> b
$ [GameType]
allGameTypesInSGFOrder
type Collection = [Game]
type Application = String
type Version = String
type Point = (Integer, Integer)
type AutoMarkup = Bool
data FuzzyBool = Possibly | Definitely deriving (FuzzyBool -> FuzzyBool -> Bool
(FuzzyBool -> FuzzyBool -> Bool)
-> (FuzzyBool -> FuzzyBool -> Bool) -> Eq FuzzyBool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FuzzyBool -> FuzzyBool -> Bool
== :: FuzzyBool -> FuzzyBool -> Bool
$c/= :: FuzzyBool -> FuzzyBool -> Bool
/= :: FuzzyBool -> FuzzyBool -> Bool
Eq, Eq FuzzyBool
Eq FuzzyBool =>
(FuzzyBool -> FuzzyBool -> Ordering)
-> (FuzzyBool -> FuzzyBool -> Bool)
-> (FuzzyBool -> FuzzyBool -> Bool)
-> (FuzzyBool -> FuzzyBool -> Bool)
-> (FuzzyBool -> FuzzyBool -> Bool)
-> (FuzzyBool -> FuzzyBool -> FuzzyBool)
-> (FuzzyBool -> FuzzyBool -> FuzzyBool)
-> Ord FuzzyBool
FuzzyBool -> FuzzyBool -> Bool
FuzzyBool -> FuzzyBool -> Ordering
FuzzyBool -> FuzzyBool -> FuzzyBool
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FuzzyBool -> FuzzyBool -> Ordering
compare :: FuzzyBool -> FuzzyBool -> Ordering
$c< :: FuzzyBool -> FuzzyBool -> Bool
< :: FuzzyBool -> FuzzyBool -> Bool
$c<= :: FuzzyBool -> FuzzyBool -> Bool
<= :: FuzzyBool -> FuzzyBool -> Bool
$c> :: FuzzyBool -> FuzzyBool -> Bool
> :: FuzzyBool -> FuzzyBool -> Bool
$c>= :: FuzzyBool -> FuzzyBool -> Bool
>= :: FuzzyBool -> FuzzyBool -> Bool
$cmax :: FuzzyBool -> FuzzyBool -> FuzzyBool
max :: FuzzyBool -> FuzzyBool -> FuzzyBool
$cmin :: FuzzyBool -> FuzzyBool -> FuzzyBool
min :: FuzzyBool -> FuzzyBool -> FuzzyBool
Ord, Int -> FuzzyBool -> ShowS
[FuzzyBool] -> ShowS
FuzzyBool -> String
(Int -> FuzzyBool -> ShowS)
-> (FuzzyBool -> String)
-> ([FuzzyBool] -> ShowS)
-> Show FuzzyBool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FuzzyBool -> ShowS
showsPrec :: Int -> FuzzyBool -> ShowS
$cshow :: FuzzyBool -> String
show :: FuzzyBool -> String
$cshowList :: [FuzzyBool] -> ShowS
showList :: [FuzzyBool] -> ShowS
Show, ReadPrec [FuzzyBool]
ReadPrec FuzzyBool
Int -> ReadS FuzzyBool
ReadS [FuzzyBool]
(Int -> ReadS FuzzyBool)
-> ReadS [FuzzyBool]
-> ReadPrec FuzzyBool
-> ReadPrec [FuzzyBool]
-> Read FuzzyBool
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FuzzyBool
readsPrec :: Int -> ReadS FuzzyBool
$creadList :: ReadS [FuzzyBool]
readList :: ReadS [FuzzyBool]
$creadPrec :: ReadPrec FuzzyBool
readPrec :: ReadPrec FuzzyBool
$creadListPrec :: ReadPrec [FuzzyBool]
readListPrec :: ReadPrec [FuzzyBool]
Read, Int -> FuzzyBool
FuzzyBool -> Int
FuzzyBool -> [FuzzyBool]
FuzzyBool -> FuzzyBool
FuzzyBool -> FuzzyBool -> [FuzzyBool]
FuzzyBool -> FuzzyBool -> FuzzyBool -> [FuzzyBool]
(FuzzyBool -> FuzzyBool)
-> (FuzzyBool -> FuzzyBool)
-> (Int -> FuzzyBool)
-> (FuzzyBool -> Int)
-> (FuzzyBool -> [FuzzyBool])
-> (FuzzyBool -> FuzzyBool -> [FuzzyBool])
-> (FuzzyBool -> FuzzyBool -> [FuzzyBool])
-> (FuzzyBool -> FuzzyBool -> FuzzyBool -> [FuzzyBool])
-> Enum FuzzyBool
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FuzzyBool -> FuzzyBool
succ :: FuzzyBool -> FuzzyBool
$cpred :: FuzzyBool -> FuzzyBool
pred :: FuzzyBool -> FuzzyBool
$ctoEnum :: Int -> FuzzyBool
toEnum :: Int -> FuzzyBool
$cfromEnum :: FuzzyBool -> Int
fromEnum :: FuzzyBool -> Int
$cenumFrom :: FuzzyBool -> [FuzzyBool]
enumFrom :: FuzzyBool -> [FuzzyBool]
$cenumFromThen :: FuzzyBool -> FuzzyBool -> [FuzzyBool]
enumFromThen :: FuzzyBool -> FuzzyBool -> [FuzzyBool]
$cenumFromTo :: FuzzyBool -> FuzzyBool -> [FuzzyBool]
enumFromTo :: FuzzyBool -> FuzzyBool -> [FuzzyBool]
$cenumFromThenTo :: FuzzyBool -> FuzzyBool -> FuzzyBool -> [FuzzyBool]
enumFromThenTo :: FuzzyBool -> FuzzyBool -> FuzzyBool -> [FuzzyBool]
Enum, FuzzyBool
FuzzyBool -> FuzzyBool -> Bounded FuzzyBool
forall a. a -> a -> Bounded a
$cminBound :: FuzzyBool
minBound :: FuzzyBool
$cmaxBound :: FuzzyBool
maxBound :: FuzzyBool
Bounded)
data Emphasis = Normal | Strong deriving (Emphasis -> Emphasis -> Bool
(Emphasis -> Emphasis -> Bool)
-> (Emphasis -> Emphasis -> Bool) -> Eq Emphasis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Emphasis -> Emphasis -> Bool
== :: Emphasis -> Emphasis -> Bool
$c/= :: Emphasis -> Emphasis -> Bool
/= :: Emphasis -> Emphasis -> Bool
Eq, Eq Emphasis
Eq Emphasis =>
(Emphasis -> Emphasis -> Ordering)
-> (Emphasis -> Emphasis -> Bool)
-> (Emphasis -> Emphasis -> Bool)
-> (Emphasis -> Emphasis -> Bool)
-> (Emphasis -> Emphasis -> Bool)
-> (Emphasis -> Emphasis -> Emphasis)
-> (Emphasis -> Emphasis -> Emphasis)
-> Ord Emphasis
Emphasis -> Emphasis -> Bool
Emphasis -> Emphasis -> Ordering
Emphasis -> Emphasis -> Emphasis
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Emphasis -> Emphasis -> Ordering
compare :: Emphasis -> Emphasis -> Ordering
$c< :: Emphasis -> Emphasis -> Bool
< :: Emphasis -> Emphasis -> Bool
$c<= :: Emphasis -> Emphasis -> Bool
<= :: Emphasis -> Emphasis -> Bool
$c> :: Emphasis -> Emphasis -> Bool
> :: Emphasis -> Emphasis -> Bool
$c>= :: Emphasis -> Emphasis -> Bool
>= :: Emphasis -> Emphasis -> Bool
$cmax :: Emphasis -> Emphasis -> Emphasis
max :: Emphasis -> Emphasis -> Emphasis
$cmin :: Emphasis -> Emphasis -> Emphasis
min :: Emphasis -> Emphasis -> Emphasis
Ord, Int -> Emphasis -> ShowS
[Emphasis] -> ShowS
Emphasis -> String
(Int -> Emphasis -> ShowS)
-> (Emphasis -> String) -> ([Emphasis] -> ShowS) -> Show Emphasis
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Emphasis -> ShowS
showsPrec :: Int -> Emphasis -> ShowS
$cshow :: Emphasis -> String
show :: Emphasis -> String
$cshowList :: [Emphasis] -> ShowS
showList :: [Emphasis] -> ShowS
Show, ReadPrec [Emphasis]
ReadPrec Emphasis
Int -> ReadS Emphasis
ReadS [Emphasis]
(Int -> ReadS Emphasis)
-> ReadS [Emphasis]
-> ReadPrec Emphasis
-> ReadPrec [Emphasis]
-> Read Emphasis
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Emphasis
readsPrec :: Int -> ReadS Emphasis
$creadList :: ReadS [Emphasis]
readList :: ReadS [Emphasis]
$creadPrec :: ReadPrec Emphasis
readPrec :: ReadPrec Emphasis
$creadListPrec :: ReadPrec [Emphasis]
readListPrec :: ReadPrec [Emphasis]
Read, Int -> Emphasis
Emphasis -> Int
Emphasis -> [Emphasis]
Emphasis -> Emphasis
Emphasis -> Emphasis -> [Emphasis]
Emphasis -> Emphasis -> Emphasis -> [Emphasis]
(Emphasis -> Emphasis)
-> (Emphasis -> Emphasis)
-> (Int -> Emphasis)
-> (Emphasis -> Int)
-> (Emphasis -> [Emphasis])
-> (Emphasis -> Emphasis -> [Emphasis])
-> (Emphasis -> Emphasis -> [Emphasis])
-> (Emphasis -> Emphasis -> Emphasis -> [Emphasis])
-> Enum Emphasis
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Emphasis -> Emphasis
succ :: Emphasis -> Emphasis
$cpred :: Emphasis -> Emphasis
pred :: Emphasis -> Emphasis
$ctoEnum :: Int -> Emphasis
toEnum :: Int -> Emphasis
$cfromEnum :: Emphasis -> Int
fromEnum :: Emphasis -> Int
$cenumFrom :: Emphasis -> [Emphasis]
enumFrom :: Emphasis -> [Emphasis]
$cenumFromThen :: Emphasis -> Emphasis -> [Emphasis]
enumFromThen :: Emphasis -> Emphasis -> [Emphasis]
$cenumFromTo :: Emphasis -> Emphasis -> [Emphasis]
enumFromTo :: Emphasis -> Emphasis -> [Emphasis]
$cenumFromThenTo :: Emphasis -> Emphasis -> Emphasis -> [Emphasis]
enumFromThenTo :: Emphasis -> Emphasis -> Emphasis -> [Emphasis]
Enum, Emphasis
Emphasis -> Emphasis -> Bounded Emphasis
forall a. a -> a -> Bounded a
$cminBound :: Emphasis
minBound :: Emphasis
$cmaxBound :: Emphasis
maxBound :: Emphasis
Bounded)
data Color = Black | White deriving (Color -> Color -> Bool
(Color -> Color -> Bool) -> (Color -> Color -> Bool) -> Eq Color
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
/= :: Color -> Color -> Bool
Eq, Eq Color
Eq Color =>
(Color -> Color -> Ordering)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Color)
-> (Color -> Color -> Color)
-> Ord Color
Color -> Color -> Bool
Color -> Color -> Ordering
Color -> Color -> Color
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Color -> Color -> Ordering
compare :: Color -> Color -> Ordering
$c< :: Color -> Color -> Bool
< :: Color -> Color -> Bool
$c<= :: Color -> Color -> Bool
<= :: Color -> Color -> Bool
$c> :: Color -> Color -> Bool
> :: Color -> Color -> Bool
$c>= :: Color -> Color -> Bool
>= :: Color -> Color -> Bool
$cmax :: Color -> Color -> Color
max :: Color -> Color -> Color
$cmin :: Color -> Color -> Color
min :: Color -> Color -> Color
Ord, Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
(Int -> Color -> ShowS)
-> (Color -> String) -> ([Color] -> ShowS) -> Show Color
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Color -> ShowS
showsPrec :: Int -> Color -> ShowS
$cshow :: Color -> String
show :: Color -> String
$cshowList :: [Color] -> ShowS
showList :: [Color] -> ShowS
Show, ReadPrec [Color]
ReadPrec Color
Int -> ReadS Color
ReadS [Color]
(Int -> ReadS Color)
-> ReadS [Color]
-> ReadPrec Color
-> ReadPrec [Color]
-> Read Color
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Color
readsPrec :: Int -> ReadS Color
$creadList :: ReadS [Color]
readList :: ReadS [Color]
$creadPrec :: ReadPrec Color
readPrec :: ReadPrec Color
$creadListPrec :: ReadPrec [Color]
readListPrec :: ReadPrec [Color]
Read, Int -> Color
Color -> Int
Color -> [Color]
Color -> Color
Color -> Color -> [Color]
Color -> Color -> Color -> [Color]
(Color -> Color)
-> (Color -> Color)
-> (Int -> Color)
-> (Color -> Int)
-> (Color -> [Color])
-> (Color -> Color -> [Color])
-> (Color -> Color -> [Color])
-> (Color -> Color -> Color -> [Color])
-> Enum Color
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Color -> Color
succ :: Color -> Color
$cpred :: Color -> Color
pred :: Color -> Color
$ctoEnum :: Int -> Color
toEnum :: Int -> Color
$cfromEnum :: Color -> Int
fromEnum :: Color -> Int
$cenumFrom :: Color -> [Color]
enumFrom :: Color -> [Color]
$cenumFromThen :: Color -> Color -> [Color]
enumFromThen :: Color -> Color -> [Color]
$cenumFromTo :: Color -> Color -> [Color]
enumFromTo :: Color -> Color -> [Color]
$cenumFromThenTo :: Color -> Color -> Color -> [Color]
enumFromThenTo :: Color -> Color -> Color -> [Color]
Enum, Color
Color -> Color -> Bounded Color
forall a. a -> a -> Bounded a
$cminBound :: Color
minBound :: Color
$cmaxBound :: Color
maxBound :: Color
Bounded)
data Certainty = Uncertain | Certain deriving (Certainty -> Certainty -> Bool
(Certainty -> Certainty -> Bool)
-> (Certainty -> Certainty -> Bool) -> Eq Certainty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Certainty -> Certainty -> Bool
== :: Certainty -> Certainty -> Bool
$c/= :: Certainty -> Certainty -> Bool
/= :: Certainty -> Certainty -> Bool
Eq, Eq Certainty
Eq Certainty =>
(Certainty -> Certainty -> Ordering)
-> (Certainty -> Certainty -> Bool)
-> (Certainty -> Certainty -> Bool)
-> (Certainty -> Certainty -> Bool)
-> (Certainty -> Certainty -> Bool)
-> (Certainty -> Certainty -> Certainty)
-> (Certainty -> Certainty -> Certainty)
-> Ord Certainty
Certainty -> Certainty -> Bool
Certainty -> Certainty -> Ordering
Certainty -> Certainty -> Certainty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Certainty -> Certainty -> Ordering
compare :: Certainty -> Certainty -> Ordering
$c< :: Certainty -> Certainty -> Bool
< :: Certainty -> Certainty -> Bool
$c<= :: Certainty -> Certainty -> Bool
<= :: Certainty -> Certainty -> Bool
$c> :: Certainty -> Certainty -> Bool
> :: Certainty -> Certainty -> Bool
$c>= :: Certainty -> Certainty -> Bool
>= :: Certainty -> Certainty -> Bool
$cmax :: Certainty -> Certainty -> Certainty
max :: Certainty -> Certainty -> Certainty
$cmin :: Certainty -> Certainty -> Certainty
min :: Certainty -> Certainty -> Certainty
Ord, Int -> Certainty -> ShowS
[Certainty] -> ShowS
Certainty -> String
(Int -> Certainty -> ShowS)
-> (Certainty -> String)
-> ([Certainty] -> ShowS)
-> Show Certainty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Certainty -> ShowS
showsPrec :: Int -> Certainty -> ShowS
$cshow :: Certainty -> String
show :: Certainty -> String
$cshowList :: [Certainty] -> ShowS
showList :: [Certainty] -> ShowS
Show, ReadPrec [Certainty]
ReadPrec Certainty
Int -> ReadS Certainty
ReadS [Certainty]
(Int -> ReadS Certainty)
-> ReadS [Certainty]
-> ReadPrec Certainty
-> ReadPrec [Certainty]
-> Read Certainty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Certainty
readsPrec :: Int -> ReadS Certainty
$creadList :: ReadS [Certainty]
readList :: ReadS [Certainty]
$creadPrec :: ReadPrec Certainty
readPrec :: ReadPrec Certainty
$creadListPrec :: ReadPrec [Certainty]
readListPrec :: ReadPrec [Certainty]
Read, Int -> Certainty
Certainty -> Int
Certainty -> [Certainty]
Certainty -> Certainty
Certainty -> Certainty -> [Certainty]
Certainty -> Certainty -> Certainty -> [Certainty]
(Certainty -> Certainty)
-> (Certainty -> Certainty)
-> (Int -> Certainty)
-> (Certainty -> Int)
-> (Certainty -> [Certainty])
-> (Certainty -> Certainty -> [Certainty])
-> (Certainty -> Certainty -> [Certainty])
-> (Certainty -> Certainty -> Certainty -> [Certainty])
-> Enum Certainty
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Certainty -> Certainty
succ :: Certainty -> Certainty
$cpred :: Certainty -> Certainty
pred :: Certainty -> Certainty
$ctoEnum :: Int -> Certainty
toEnum :: Int -> Certainty
$cfromEnum :: Certainty -> Int
fromEnum :: Certainty -> Int
$cenumFrom :: Certainty -> [Certainty]
enumFrom :: Certainty -> [Certainty]
$cenumFromThen :: Certainty -> Certainty -> [Certainty]
enumFromThen :: Certainty -> Certainty -> [Certainty]
$cenumFromTo :: Certainty -> Certainty -> [Certainty]
enumFromTo :: Certainty -> Certainty -> [Certainty]
$cenumFromThenTo :: Certainty -> Certainty -> Certainty -> [Certainty]
enumFromThenTo :: Certainty -> Certainty -> Certainty -> [Certainty]
Enum, Certainty
Certainty -> Certainty -> Bounded Certainty
forall a. a -> a -> Bounded a
$cminBound :: Certainty
minBound :: Certainty
$cmaxBound :: Certainty
maxBound :: Certainty
Bounded)
data InitialPosition = Beginning | End deriving (InitialPosition -> InitialPosition -> Bool
(InitialPosition -> InitialPosition -> Bool)
-> (InitialPosition -> InitialPosition -> Bool)
-> Eq InitialPosition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InitialPosition -> InitialPosition -> Bool
== :: InitialPosition -> InitialPosition -> Bool
$c/= :: InitialPosition -> InitialPosition -> Bool
/= :: InitialPosition -> InitialPosition -> Bool
Eq, Eq InitialPosition
Eq InitialPosition =>
(InitialPosition -> InitialPosition -> Ordering)
-> (InitialPosition -> InitialPosition -> Bool)
-> (InitialPosition -> InitialPosition -> Bool)
-> (InitialPosition -> InitialPosition -> Bool)
-> (InitialPosition -> InitialPosition -> Bool)
-> (InitialPosition -> InitialPosition -> InitialPosition)
-> (InitialPosition -> InitialPosition -> InitialPosition)
-> Ord InitialPosition
InitialPosition -> InitialPosition -> Bool
InitialPosition -> InitialPosition -> Ordering
InitialPosition -> InitialPosition -> InitialPosition
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InitialPosition -> InitialPosition -> Ordering
compare :: InitialPosition -> InitialPosition -> Ordering
$c< :: InitialPosition -> InitialPosition -> Bool
< :: InitialPosition -> InitialPosition -> Bool
$c<= :: InitialPosition -> InitialPosition -> Bool
<= :: InitialPosition -> InitialPosition -> Bool
$c> :: InitialPosition -> InitialPosition -> Bool
> :: InitialPosition -> InitialPosition -> Bool
$c>= :: InitialPosition -> InitialPosition -> Bool
>= :: InitialPosition -> InitialPosition -> Bool
$cmax :: InitialPosition -> InitialPosition -> InitialPosition
max :: InitialPosition -> InitialPosition -> InitialPosition
$cmin :: InitialPosition -> InitialPosition -> InitialPosition
min :: InitialPosition -> InitialPosition -> InitialPosition
Ord, Int -> InitialPosition -> ShowS
[InitialPosition] -> ShowS
InitialPosition -> String
(Int -> InitialPosition -> ShowS)
-> (InitialPosition -> String)
-> ([InitialPosition] -> ShowS)
-> Show InitialPosition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InitialPosition -> ShowS
showsPrec :: Int -> InitialPosition -> ShowS
$cshow :: InitialPosition -> String
show :: InitialPosition -> String
$cshowList :: [InitialPosition] -> ShowS
showList :: [InitialPosition] -> ShowS
Show, ReadPrec [InitialPosition]
ReadPrec InitialPosition
Int -> ReadS InitialPosition
ReadS [InitialPosition]
(Int -> ReadS InitialPosition)
-> ReadS [InitialPosition]
-> ReadPrec InitialPosition
-> ReadPrec [InitialPosition]
-> Read InitialPosition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InitialPosition
readsPrec :: Int -> ReadS InitialPosition
$creadList :: ReadS [InitialPosition]
readList :: ReadS [InitialPosition]
$creadPrec :: ReadPrec InitialPosition
readPrec :: ReadPrec InitialPosition
$creadListPrec :: ReadPrec [InitialPosition]
readListPrec :: ReadPrec [InitialPosition]
Read, Int -> InitialPosition
InitialPosition -> Int
InitialPosition -> [InitialPosition]
InitialPosition -> InitialPosition
InitialPosition -> InitialPosition -> [InitialPosition]
InitialPosition
-> InitialPosition -> InitialPosition -> [InitialPosition]
(InitialPosition -> InitialPosition)
-> (InitialPosition -> InitialPosition)
-> (Int -> InitialPosition)
-> (InitialPosition -> Int)
-> (InitialPosition -> [InitialPosition])
-> (InitialPosition -> InitialPosition -> [InitialPosition])
-> (InitialPosition -> InitialPosition -> [InitialPosition])
-> (InitialPosition
-> InitialPosition -> InitialPosition -> [InitialPosition])
-> Enum InitialPosition
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: InitialPosition -> InitialPosition
succ :: InitialPosition -> InitialPosition
$cpred :: InitialPosition -> InitialPosition
pred :: InitialPosition -> InitialPosition
$ctoEnum :: Int -> InitialPosition
toEnum :: Int -> InitialPosition
$cfromEnum :: InitialPosition -> Int
fromEnum :: InitialPosition -> Int
$cenumFrom :: InitialPosition -> [InitialPosition]
enumFrom :: InitialPosition -> [InitialPosition]
$cenumFromThen :: InitialPosition -> InitialPosition -> [InitialPosition]
enumFromThen :: InitialPosition -> InitialPosition -> [InitialPosition]
$cenumFromTo :: InitialPosition -> InitialPosition -> [InitialPosition]
enumFromTo :: InitialPosition -> InitialPosition -> [InitialPosition]
$cenumFromThenTo :: InitialPosition
-> InitialPosition -> InitialPosition -> [InitialPosition]
enumFromThenTo :: InitialPosition
-> InitialPosition -> InitialPosition -> [InitialPosition]
Enum, InitialPosition
InitialPosition -> InitialPosition -> Bounded InitialPosition
forall a. a -> a -> Bounded a
$cminBound :: InitialPosition
minBound :: InitialPosition
$cmaxBound :: InitialPosition
maxBound :: InitialPosition
Bounded)
data RankScale = Kyu | Dan | Pro deriving (RankScale -> RankScale -> Bool
(RankScale -> RankScale -> Bool)
-> (RankScale -> RankScale -> Bool) -> Eq RankScale
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RankScale -> RankScale -> Bool
== :: RankScale -> RankScale -> Bool
$c/= :: RankScale -> RankScale -> Bool
/= :: RankScale -> RankScale -> Bool
Eq, Eq RankScale
Eq RankScale =>
(RankScale -> RankScale -> Ordering)
-> (RankScale -> RankScale -> Bool)
-> (RankScale -> RankScale -> Bool)
-> (RankScale -> RankScale -> Bool)
-> (RankScale -> RankScale -> Bool)
-> (RankScale -> RankScale -> RankScale)
-> (RankScale -> RankScale -> RankScale)
-> Ord RankScale
RankScale -> RankScale -> Bool
RankScale -> RankScale -> Ordering
RankScale -> RankScale -> RankScale
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RankScale -> RankScale -> Ordering
compare :: RankScale -> RankScale -> Ordering
$c< :: RankScale -> RankScale -> Bool
< :: RankScale -> RankScale -> Bool
$c<= :: RankScale -> RankScale -> Bool
<= :: RankScale -> RankScale -> Bool
$c> :: RankScale -> RankScale -> Bool
> :: RankScale -> RankScale -> Bool
$c>= :: RankScale -> RankScale -> Bool
>= :: RankScale -> RankScale -> Bool
$cmax :: RankScale -> RankScale -> RankScale
max :: RankScale -> RankScale -> RankScale
$cmin :: RankScale -> RankScale -> RankScale
min :: RankScale -> RankScale -> RankScale
Ord, Int -> RankScale -> ShowS
[RankScale] -> ShowS
RankScale -> String
(Int -> RankScale -> ShowS)
-> (RankScale -> String)
-> ([RankScale] -> ShowS)
-> Show RankScale
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RankScale -> ShowS
showsPrec :: Int -> RankScale -> ShowS
$cshow :: RankScale -> String
show :: RankScale -> String
$cshowList :: [RankScale] -> ShowS
showList :: [RankScale] -> ShowS
Show, ReadPrec [RankScale]
ReadPrec RankScale
Int -> ReadS RankScale
ReadS [RankScale]
(Int -> ReadS RankScale)
-> ReadS [RankScale]
-> ReadPrec RankScale
-> ReadPrec [RankScale]
-> Read RankScale
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RankScale
readsPrec :: Int -> ReadS RankScale
$creadList :: ReadS [RankScale]
readList :: ReadS [RankScale]
$creadPrec :: ReadPrec RankScale
readPrec :: ReadPrec RankScale
$creadListPrec :: ReadPrec [RankScale]
readListPrec :: ReadPrec [RankScale]
Read, Int -> RankScale
RankScale -> Int
RankScale -> [RankScale]
RankScale -> RankScale
RankScale -> RankScale -> [RankScale]
RankScale -> RankScale -> RankScale -> [RankScale]
(RankScale -> RankScale)
-> (RankScale -> RankScale)
-> (Int -> RankScale)
-> (RankScale -> Int)
-> (RankScale -> [RankScale])
-> (RankScale -> RankScale -> [RankScale])
-> (RankScale -> RankScale -> [RankScale])
-> (RankScale -> RankScale -> RankScale -> [RankScale])
-> Enum RankScale
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RankScale -> RankScale
succ :: RankScale -> RankScale
$cpred :: RankScale -> RankScale
pred :: RankScale -> RankScale
$ctoEnum :: Int -> RankScale
toEnum :: Int -> RankScale
$cfromEnum :: RankScale -> Int
fromEnum :: RankScale -> Int
$cenumFrom :: RankScale -> [RankScale]
enumFrom :: RankScale -> [RankScale]
$cenumFromThen :: RankScale -> RankScale -> [RankScale]
enumFromThen :: RankScale -> RankScale -> [RankScale]
$cenumFromTo :: RankScale -> RankScale -> [RankScale]
enumFromTo :: RankScale -> RankScale -> [RankScale]
$cenumFromThenTo :: RankScale -> RankScale -> RankScale -> [RankScale]
enumFromThenTo :: RankScale -> RankScale -> RankScale -> [RankScale]
Enum, RankScale
RankScale -> RankScale -> Bounded RankScale
forall a. a -> a -> Bounded a
$cminBound :: RankScale
minBound :: RankScale
$cmaxBound :: RankScale
maxBound :: RankScale
Bounded)
data Judgment = GoodForWhite | GoodForBlack | Even | Unclear deriving (Judgment -> Judgment -> Bool
(Judgment -> Judgment -> Bool)
-> (Judgment -> Judgment -> Bool) -> Eq Judgment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Judgment -> Judgment -> Bool
== :: Judgment -> Judgment -> Bool
$c/= :: Judgment -> Judgment -> Bool
/= :: Judgment -> Judgment -> Bool
Eq, Eq Judgment
Eq Judgment =>
(Judgment -> Judgment -> Ordering)
-> (Judgment -> Judgment -> Bool)
-> (Judgment -> Judgment -> Bool)
-> (Judgment -> Judgment -> Bool)
-> (Judgment -> Judgment -> Bool)
-> (Judgment -> Judgment -> Judgment)
-> (Judgment -> Judgment -> Judgment)
-> Ord Judgment
Judgment -> Judgment -> Bool
Judgment -> Judgment -> Ordering
Judgment -> Judgment -> Judgment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Judgment -> Judgment -> Ordering
compare :: Judgment -> Judgment -> Ordering
$c< :: Judgment -> Judgment -> Bool
< :: Judgment -> Judgment -> Bool
$c<= :: Judgment -> Judgment -> Bool
<= :: Judgment -> Judgment -> Bool
$c> :: Judgment -> Judgment -> Bool
> :: Judgment -> Judgment -> Bool
$c>= :: Judgment -> Judgment -> Bool
>= :: Judgment -> Judgment -> Bool
$cmax :: Judgment -> Judgment -> Judgment
max :: Judgment -> Judgment -> Judgment
$cmin :: Judgment -> Judgment -> Judgment
min :: Judgment -> Judgment -> Judgment
Ord, Int -> Judgment -> ShowS
[Judgment] -> ShowS
Judgment -> String
(Int -> Judgment -> ShowS)
-> (Judgment -> String) -> ([Judgment] -> ShowS) -> Show Judgment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Judgment -> ShowS
showsPrec :: Int -> Judgment -> ShowS
$cshow :: Judgment -> String
show :: Judgment -> String
$cshowList :: [Judgment] -> ShowS
showList :: [Judgment] -> ShowS
Show, ReadPrec [Judgment]
ReadPrec Judgment
Int -> ReadS Judgment
ReadS [Judgment]
(Int -> ReadS Judgment)
-> ReadS [Judgment]
-> ReadPrec Judgment
-> ReadPrec [Judgment]
-> Read Judgment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Judgment
readsPrec :: Int -> ReadS Judgment
$creadList :: ReadS [Judgment]
readList :: ReadS [Judgment]
$creadPrec :: ReadPrec Judgment
readPrec :: ReadPrec Judgment
$creadListPrec :: ReadPrec [Judgment]
readListPrec :: ReadPrec [Judgment]
Read, Int -> Judgment
Judgment -> Int
Judgment -> [Judgment]
Judgment -> Judgment
Judgment -> Judgment -> [Judgment]
Judgment -> Judgment -> Judgment -> [Judgment]
(Judgment -> Judgment)
-> (Judgment -> Judgment)
-> (Int -> Judgment)
-> (Judgment -> Int)
-> (Judgment -> [Judgment])
-> (Judgment -> Judgment -> [Judgment])
-> (Judgment -> Judgment -> [Judgment])
-> (Judgment -> Judgment -> Judgment -> [Judgment])
-> Enum Judgment
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Judgment -> Judgment
succ :: Judgment -> Judgment
$cpred :: Judgment -> Judgment
pred :: Judgment -> Judgment
$ctoEnum :: Int -> Judgment
toEnum :: Int -> Judgment
$cfromEnum :: Judgment -> Int
fromEnum :: Judgment -> Int
$cenumFrom :: Judgment -> [Judgment]
enumFrom :: Judgment -> [Judgment]
$cenumFromThen :: Judgment -> Judgment -> [Judgment]
enumFromThen :: Judgment -> Judgment -> [Judgment]
$cenumFromTo :: Judgment -> Judgment -> [Judgment]
enumFromTo :: Judgment -> Judgment -> [Judgment]
$cenumFromThenTo :: Judgment -> Judgment -> Judgment -> [Judgment]
enumFromThenTo :: Judgment -> Judgment -> Judgment -> [Judgment]
Enum, Judgment
Judgment -> Judgment -> Bounded Judgment
forall a. a -> a -> Bounded a
$cminBound :: Judgment
minBound :: Judgment
$cmaxBound :: Judgment
maxBound :: Judgment
Bounded)
data InitialPlacement = Standard | ScrambledEggs | Parachute | Gemma | Custom deriving (InitialPlacement -> InitialPlacement -> Bool
(InitialPlacement -> InitialPlacement -> Bool)
-> (InitialPlacement -> InitialPlacement -> Bool)
-> Eq InitialPlacement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InitialPlacement -> InitialPlacement -> Bool
== :: InitialPlacement -> InitialPlacement -> Bool
$c/= :: InitialPlacement -> InitialPlacement -> Bool
/= :: InitialPlacement -> InitialPlacement -> Bool
Eq, Eq InitialPlacement
Eq InitialPlacement =>
(InitialPlacement -> InitialPlacement -> Ordering)
-> (InitialPlacement -> InitialPlacement -> Bool)
-> (InitialPlacement -> InitialPlacement -> Bool)
-> (InitialPlacement -> InitialPlacement -> Bool)
-> (InitialPlacement -> InitialPlacement -> Bool)
-> (InitialPlacement -> InitialPlacement -> InitialPlacement)
-> (InitialPlacement -> InitialPlacement -> InitialPlacement)
-> Ord InitialPlacement
InitialPlacement -> InitialPlacement -> Bool
InitialPlacement -> InitialPlacement -> Ordering
InitialPlacement -> InitialPlacement -> InitialPlacement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InitialPlacement -> InitialPlacement -> Ordering
compare :: InitialPlacement -> InitialPlacement -> Ordering
$c< :: InitialPlacement -> InitialPlacement -> Bool
< :: InitialPlacement -> InitialPlacement -> Bool
$c<= :: InitialPlacement -> InitialPlacement -> Bool
<= :: InitialPlacement -> InitialPlacement -> Bool
$c> :: InitialPlacement -> InitialPlacement -> Bool
> :: InitialPlacement -> InitialPlacement -> Bool
$c>= :: InitialPlacement -> InitialPlacement -> Bool
>= :: InitialPlacement -> InitialPlacement -> Bool
$cmax :: InitialPlacement -> InitialPlacement -> InitialPlacement
max :: InitialPlacement -> InitialPlacement -> InitialPlacement
$cmin :: InitialPlacement -> InitialPlacement -> InitialPlacement
min :: InitialPlacement -> InitialPlacement -> InitialPlacement
Ord, Int -> InitialPlacement -> ShowS
[InitialPlacement] -> ShowS
InitialPlacement -> String
(Int -> InitialPlacement -> ShowS)
-> (InitialPlacement -> String)
-> ([InitialPlacement] -> ShowS)
-> Show InitialPlacement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InitialPlacement -> ShowS
showsPrec :: Int -> InitialPlacement -> ShowS
$cshow :: InitialPlacement -> String
show :: InitialPlacement -> String
$cshowList :: [InitialPlacement] -> ShowS
showList :: [InitialPlacement] -> ShowS
Show, ReadPrec [InitialPlacement]
ReadPrec InitialPlacement
Int -> ReadS InitialPlacement
ReadS [InitialPlacement]
(Int -> ReadS InitialPlacement)
-> ReadS [InitialPlacement]
-> ReadPrec InitialPlacement
-> ReadPrec [InitialPlacement]
-> Read InitialPlacement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InitialPlacement
readsPrec :: Int -> ReadS InitialPlacement
$creadList :: ReadS [InitialPlacement]
readList :: ReadS [InitialPlacement]
$creadPrec :: ReadPrec InitialPlacement
readPrec :: ReadPrec InitialPlacement
$creadListPrec :: ReadPrec [InitialPlacement]
readListPrec :: ReadPrec [InitialPlacement]
Read, Int -> InitialPlacement
InitialPlacement -> Int
InitialPlacement -> [InitialPlacement]
InitialPlacement -> InitialPlacement
InitialPlacement -> InitialPlacement -> [InitialPlacement]
InitialPlacement
-> InitialPlacement -> InitialPlacement -> [InitialPlacement]
(InitialPlacement -> InitialPlacement)
-> (InitialPlacement -> InitialPlacement)
-> (Int -> InitialPlacement)
-> (InitialPlacement -> Int)
-> (InitialPlacement -> [InitialPlacement])
-> (InitialPlacement -> InitialPlacement -> [InitialPlacement])
-> (InitialPlacement -> InitialPlacement -> [InitialPlacement])
-> (InitialPlacement
-> InitialPlacement -> InitialPlacement -> [InitialPlacement])
-> Enum InitialPlacement
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: InitialPlacement -> InitialPlacement
succ :: InitialPlacement -> InitialPlacement
$cpred :: InitialPlacement -> InitialPlacement
pred :: InitialPlacement -> InitialPlacement
$ctoEnum :: Int -> InitialPlacement
toEnum :: Int -> InitialPlacement
$cfromEnum :: InitialPlacement -> Int
fromEnum :: InitialPlacement -> Int
$cenumFrom :: InitialPlacement -> [InitialPlacement]
enumFrom :: InitialPlacement -> [InitialPlacement]
$cenumFromThen :: InitialPlacement -> InitialPlacement -> [InitialPlacement]
enumFromThen :: InitialPlacement -> InitialPlacement -> [InitialPlacement]
$cenumFromTo :: InitialPlacement -> InitialPlacement -> [InitialPlacement]
enumFromTo :: InitialPlacement -> InitialPlacement -> [InitialPlacement]
$cenumFromThenTo :: InitialPlacement
-> InitialPlacement -> InitialPlacement -> [InitialPlacement]
enumFromThenTo :: InitialPlacement
-> InitialPlacement -> InitialPlacement -> [InitialPlacement]
Enum, InitialPlacement
InitialPlacement -> InitialPlacement -> Bounded InitialPlacement
forall a. a -> a -> Bounded a
$cminBound :: InitialPlacement
minBound :: InitialPlacement
$cmaxBound :: InitialPlacement
maxBound :: InitialPlacement
Bounded)
data VariationType
= Children
| Siblings
deriving (VariationType -> VariationType -> Bool
(VariationType -> VariationType -> Bool)
-> (VariationType -> VariationType -> Bool) -> Eq VariationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariationType -> VariationType -> Bool
== :: VariationType -> VariationType -> Bool
$c/= :: VariationType -> VariationType -> Bool
/= :: VariationType -> VariationType -> Bool
Eq, Eq VariationType
Eq VariationType =>
(VariationType -> VariationType -> Ordering)
-> (VariationType -> VariationType -> Bool)
-> (VariationType -> VariationType -> Bool)
-> (VariationType -> VariationType -> Bool)
-> (VariationType -> VariationType -> Bool)
-> (VariationType -> VariationType -> VariationType)
-> (VariationType -> VariationType -> VariationType)
-> Ord VariationType
VariationType -> VariationType -> Bool
VariationType -> VariationType -> Ordering
VariationType -> VariationType -> VariationType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VariationType -> VariationType -> Ordering
compare :: VariationType -> VariationType -> Ordering
$c< :: VariationType -> VariationType -> Bool
< :: VariationType -> VariationType -> Bool
$c<= :: VariationType -> VariationType -> Bool
<= :: VariationType -> VariationType -> Bool
$c> :: VariationType -> VariationType -> Bool
> :: VariationType -> VariationType -> Bool
$c>= :: VariationType -> VariationType -> Bool
>= :: VariationType -> VariationType -> Bool
$cmax :: VariationType -> VariationType -> VariationType
max :: VariationType -> VariationType -> VariationType
$cmin :: VariationType -> VariationType -> VariationType
min :: VariationType -> VariationType -> VariationType
Ord, Int -> VariationType -> ShowS
[VariationType] -> ShowS
VariationType -> String
(Int -> VariationType -> ShowS)
-> (VariationType -> String)
-> ([VariationType] -> ShowS)
-> Show VariationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariationType -> ShowS
showsPrec :: Int -> VariationType -> ShowS
$cshow :: VariationType -> String
show :: VariationType -> String
$cshowList :: [VariationType] -> ShowS
showList :: [VariationType] -> ShowS
Show, ReadPrec [VariationType]
ReadPrec VariationType
Int -> ReadS VariationType
ReadS [VariationType]
(Int -> ReadS VariationType)
-> ReadS [VariationType]
-> ReadPrec VariationType
-> ReadPrec [VariationType]
-> Read VariationType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VariationType
readsPrec :: Int -> ReadS VariationType
$creadList :: ReadS [VariationType]
readList :: ReadS [VariationType]
$creadPrec :: ReadPrec VariationType
readPrec :: ReadPrec VariationType
$creadListPrec :: ReadPrec [VariationType]
readListPrec :: ReadPrec [VariationType]
Read, Int -> VariationType
VariationType -> Int
VariationType -> [VariationType]
VariationType -> VariationType
VariationType -> VariationType -> [VariationType]
VariationType -> VariationType -> VariationType -> [VariationType]
(VariationType -> VariationType)
-> (VariationType -> VariationType)
-> (Int -> VariationType)
-> (VariationType -> Int)
-> (VariationType -> [VariationType])
-> (VariationType -> VariationType -> [VariationType])
-> (VariationType -> VariationType -> [VariationType])
-> (VariationType
-> VariationType -> VariationType -> [VariationType])
-> Enum VariationType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: VariationType -> VariationType
succ :: VariationType -> VariationType
$cpred :: VariationType -> VariationType
pred :: VariationType -> VariationType
$ctoEnum :: Int -> VariationType
toEnum :: Int -> VariationType
$cfromEnum :: VariationType -> Int
fromEnum :: VariationType -> Int
$cenumFrom :: VariationType -> [VariationType]
enumFrom :: VariationType -> [VariationType]
$cenumFromThen :: VariationType -> VariationType -> [VariationType]
enumFromThen :: VariationType -> VariationType -> [VariationType]
$cenumFromTo :: VariationType -> VariationType -> [VariationType]
enumFromTo :: VariationType -> VariationType -> [VariationType]
$cenumFromThenTo :: VariationType -> VariationType -> VariationType -> [VariationType]
enumFromThenTo :: VariationType -> VariationType -> VariationType -> [VariationType]
Enum, VariationType
VariationType -> VariationType -> Bounded VariationType
forall a. a -> a -> Bounded a
$cminBound :: VariationType
minBound :: VariationType
$cmaxBound :: VariationType
maxBound :: VariationType
Bounded)
data Mark
= Circle
| X
| Selected
| Square
| Triangle
deriving (Mark -> Mark -> Bool
(Mark -> Mark -> Bool) -> (Mark -> Mark -> Bool) -> Eq Mark
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Mark -> Mark -> Bool
== :: Mark -> Mark -> Bool
$c/= :: Mark -> Mark -> Bool
/= :: Mark -> Mark -> Bool
Eq, Eq Mark
Eq Mark =>
(Mark -> Mark -> Ordering)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Mark)
-> (Mark -> Mark -> Mark)
-> Ord Mark
Mark -> Mark -> Bool
Mark -> Mark -> Ordering
Mark -> Mark -> Mark
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Mark -> Mark -> Ordering
compare :: Mark -> Mark -> Ordering
$c< :: Mark -> Mark -> Bool
< :: Mark -> Mark -> Bool
$c<= :: Mark -> Mark -> Bool
<= :: Mark -> Mark -> Bool
$c> :: Mark -> Mark -> Bool
> :: Mark -> Mark -> Bool
$c>= :: Mark -> Mark -> Bool
>= :: Mark -> Mark -> Bool
$cmax :: Mark -> Mark -> Mark
max :: Mark -> Mark -> Mark
$cmin :: Mark -> Mark -> Mark
min :: Mark -> Mark -> Mark
Ord, Int -> Mark -> ShowS
[Mark] -> ShowS
Mark -> String
(Int -> Mark -> ShowS)
-> (Mark -> String) -> ([Mark] -> ShowS) -> Show Mark
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Mark -> ShowS
showsPrec :: Int -> Mark -> ShowS
$cshow :: Mark -> String
show :: Mark -> String
$cshowList :: [Mark] -> ShowS
showList :: [Mark] -> ShowS
Show, ReadPrec [Mark]
ReadPrec Mark
Int -> ReadS Mark
ReadS [Mark]
(Int -> ReadS Mark)
-> ReadS [Mark] -> ReadPrec Mark -> ReadPrec [Mark] -> Read Mark
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Mark
readsPrec :: Int -> ReadS Mark
$creadList :: ReadS [Mark]
readList :: ReadS [Mark]
$creadPrec :: ReadPrec Mark
readPrec :: ReadPrec Mark
$creadListPrec :: ReadPrec [Mark]
readListPrec :: ReadPrec [Mark]
Read, Int -> Mark
Mark -> Int
Mark -> [Mark]
Mark -> Mark
Mark -> Mark -> [Mark]
Mark -> Mark -> Mark -> [Mark]
(Mark -> Mark)
-> (Mark -> Mark)
-> (Int -> Mark)
-> (Mark -> Int)
-> (Mark -> [Mark])
-> (Mark -> Mark -> [Mark])
-> (Mark -> Mark -> [Mark])
-> (Mark -> Mark -> Mark -> [Mark])
-> Enum Mark
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Mark -> Mark
succ :: Mark -> Mark
$cpred :: Mark -> Mark
pred :: Mark -> Mark
$ctoEnum :: Int -> Mark
toEnum :: Int -> Mark
$cfromEnum :: Mark -> Int
fromEnum :: Mark -> Int
$cenumFrom :: Mark -> [Mark]
enumFrom :: Mark -> [Mark]
$cenumFromThen :: Mark -> Mark -> [Mark]
enumFromThen :: Mark -> Mark -> [Mark]
$cenumFromTo :: Mark -> Mark -> [Mark]
enumFromTo :: Mark -> Mark -> [Mark]
$cenumFromThenTo :: Mark -> Mark -> Mark -> [Mark]
enumFromThenTo :: Mark -> Mark -> Mark -> [Mark]
Enum, Mark
Mark -> Mark -> Bounded Mark
forall a. a -> a -> Bounded a
$cminBound :: Mark
minBound :: Mark
$cmaxBound :: Mark
maxBound :: Mark
Bounded)
data GameInfoType
= TeamName Color
| PlayerName Color
| Annotator
| Source
| User
| Copyright
| Context
| Location
| Event
| GameName
| Opening
| Overtime
deriving (GameInfoType -> GameInfoType -> Bool
(GameInfoType -> GameInfoType -> Bool)
-> (GameInfoType -> GameInfoType -> Bool) -> Eq GameInfoType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameInfoType -> GameInfoType -> Bool
== :: GameInfoType -> GameInfoType -> Bool
$c/= :: GameInfoType -> GameInfoType -> Bool
/= :: GameInfoType -> GameInfoType -> Bool
Eq, Eq GameInfoType
Eq GameInfoType =>
(GameInfoType -> GameInfoType -> Ordering)
-> (GameInfoType -> GameInfoType -> Bool)
-> (GameInfoType -> GameInfoType -> Bool)
-> (GameInfoType -> GameInfoType -> Bool)
-> (GameInfoType -> GameInfoType -> Bool)
-> (GameInfoType -> GameInfoType -> GameInfoType)
-> (GameInfoType -> GameInfoType -> GameInfoType)
-> Ord GameInfoType
GameInfoType -> GameInfoType -> Bool
GameInfoType -> GameInfoType -> Ordering
GameInfoType -> GameInfoType -> GameInfoType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameInfoType -> GameInfoType -> Ordering
compare :: GameInfoType -> GameInfoType -> Ordering
$c< :: GameInfoType -> GameInfoType -> Bool
< :: GameInfoType -> GameInfoType -> Bool
$c<= :: GameInfoType -> GameInfoType -> Bool
<= :: GameInfoType -> GameInfoType -> Bool
$c> :: GameInfoType -> GameInfoType -> Bool
> :: GameInfoType -> GameInfoType -> Bool
$c>= :: GameInfoType -> GameInfoType -> Bool
>= :: GameInfoType -> GameInfoType -> Bool
$cmax :: GameInfoType -> GameInfoType -> GameInfoType
max :: GameInfoType -> GameInfoType -> GameInfoType
$cmin :: GameInfoType -> GameInfoType -> GameInfoType
min :: GameInfoType -> GameInfoType -> GameInfoType
Ord, Int -> GameInfoType -> ShowS
[GameInfoType] -> ShowS
GameInfoType -> String
(Int -> GameInfoType -> ShowS)
-> (GameInfoType -> String)
-> ([GameInfoType] -> ShowS)
-> Show GameInfoType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameInfoType -> ShowS
showsPrec :: Int -> GameInfoType -> ShowS
$cshow :: GameInfoType -> String
show :: GameInfoType -> String
$cshowList :: [GameInfoType] -> ShowS
showList :: [GameInfoType] -> ShowS
Show, ReadPrec [GameInfoType]
ReadPrec GameInfoType
Int -> ReadS GameInfoType
ReadS [GameInfoType]
(Int -> ReadS GameInfoType)
-> ReadS [GameInfoType]
-> ReadPrec GameInfoType
-> ReadPrec [GameInfoType]
-> Read GameInfoType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameInfoType
readsPrec :: Int -> ReadS GameInfoType
$creadList :: ReadS [GameInfoType]
readList :: ReadS [GameInfoType]
$creadPrec :: ReadPrec GameInfoType
readPrec :: ReadPrec GameInfoType
$creadListPrec :: ReadPrec [GameInfoType]
readListPrec :: ReadPrec [GameInfoType]
Read)
data ViewerSetting
= Tried
| Marked
| LastMove
| Headings
| Lock
deriving (ViewerSetting -> ViewerSetting -> Bool
(ViewerSetting -> ViewerSetting -> Bool)
-> (ViewerSetting -> ViewerSetting -> Bool) -> Eq ViewerSetting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ViewerSetting -> ViewerSetting -> Bool
== :: ViewerSetting -> ViewerSetting -> Bool
$c/= :: ViewerSetting -> ViewerSetting -> Bool
/= :: ViewerSetting -> ViewerSetting -> Bool
Eq, Eq ViewerSetting
Eq ViewerSetting =>
(ViewerSetting -> ViewerSetting -> Ordering)
-> (ViewerSetting -> ViewerSetting -> Bool)
-> (ViewerSetting -> ViewerSetting -> Bool)
-> (ViewerSetting -> ViewerSetting -> Bool)
-> (ViewerSetting -> ViewerSetting -> Bool)
-> (ViewerSetting -> ViewerSetting -> ViewerSetting)
-> (ViewerSetting -> ViewerSetting -> ViewerSetting)
-> Ord ViewerSetting
ViewerSetting -> ViewerSetting -> Bool
ViewerSetting -> ViewerSetting -> Ordering
ViewerSetting -> ViewerSetting -> ViewerSetting
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ViewerSetting -> ViewerSetting -> Ordering
compare :: ViewerSetting -> ViewerSetting -> Ordering
$c< :: ViewerSetting -> ViewerSetting -> Bool
< :: ViewerSetting -> ViewerSetting -> Bool
$c<= :: ViewerSetting -> ViewerSetting -> Bool
<= :: ViewerSetting -> ViewerSetting -> Bool
$c> :: ViewerSetting -> ViewerSetting -> Bool
> :: ViewerSetting -> ViewerSetting -> Bool
$c>= :: ViewerSetting -> ViewerSetting -> Bool
>= :: ViewerSetting -> ViewerSetting -> Bool
$cmax :: ViewerSetting -> ViewerSetting -> ViewerSetting
max :: ViewerSetting -> ViewerSetting -> ViewerSetting
$cmin :: ViewerSetting -> ViewerSetting -> ViewerSetting
min :: ViewerSetting -> ViewerSetting -> ViewerSetting
Ord, Int -> ViewerSetting -> ShowS
[ViewerSetting] -> ShowS
ViewerSetting -> String
(Int -> ViewerSetting -> ShowS)
-> (ViewerSetting -> String)
-> ([ViewerSetting] -> ShowS)
-> Show ViewerSetting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ViewerSetting -> ShowS
showsPrec :: Int -> ViewerSetting -> ShowS
$cshow :: ViewerSetting -> String
show :: ViewerSetting -> String
$cshowList :: [ViewerSetting] -> ShowS
showList :: [ViewerSetting] -> ShowS
Show, ReadPrec [ViewerSetting]
ReadPrec ViewerSetting
Int -> ReadS ViewerSetting
ReadS [ViewerSetting]
(Int -> ReadS ViewerSetting)
-> ReadS [ViewerSetting]
-> ReadPrec ViewerSetting
-> ReadPrec [ViewerSetting]
-> Read ViewerSetting
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ViewerSetting
readsPrec :: Int -> ReadS ViewerSetting
$creadList :: ReadS [ViewerSetting]
readList :: ReadS [ViewerSetting]
$creadPrec :: ReadPrec ViewerSetting
readPrec :: ReadPrec ViewerSetting
$creadListPrec :: ReadPrec [ViewerSetting]
readListPrec :: ReadPrec [ViewerSetting]
Read, Int -> ViewerSetting
ViewerSetting -> Int
ViewerSetting -> [ViewerSetting]
ViewerSetting -> ViewerSetting
ViewerSetting -> ViewerSetting -> [ViewerSetting]
ViewerSetting -> ViewerSetting -> ViewerSetting -> [ViewerSetting]
(ViewerSetting -> ViewerSetting)
-> (ViewerSetting -> ViewerSetting)
-> (Int -> ViewerSetting)
-> (ViewerSetting -> Int)
-> (ViewerSetting -> [ViewerSetting])
-> (ViewerSetting -> ViewerSetting -> [ViewerSetting])
-> (ViewerSetting -> ViewerSetting -> [ViewerSetting])
-> (ViewerSetting
-> ViewerSetting -> ViewerSetting -> [ViewerSetting])
-> Enum ViewerSetting
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ViewerSetting -> ViewerSetting
succ :: ViewerSetting -> ViewerSetting
$cpred :: ViewerSetting -> ViewerSetting
pred :: ViewerSetting -> ViewerSetting
$ctoEnum :: Int -> ViewerSetting
toEnum :: Int -> ViewerSetting
$cfromEnum :: ViewerSetting -> Int
fromEnum :: ViewerSetting -> Int
$cenumFrom :: ViewerSetting -> [ViewerSetting]
enumFrom :: ViewerSetting -> [ViewerSetting]
$cenumFromThen :: ViewerSetting -> ViewerSetting -> [ViewerSetting]
enumFromThen :: ViewerSetting -> ViewerSetting -> [ViewerSetting]
$cenumFromTo :: ViewerSetting -> ViewerSetting -> [ViewerSetting]
enumFromTo :: ViewerSetting -> ViewerSetting -> [ViewerSetting]
$cenumFromThenTo :: ViewerSetting -> ViewerSetting -> ViewerSetting -> [ViewerSetting]
enumFromThenTo :: ViewerSetting -> ViewerSetting -> ViewerSetting -> [ViewerSetting]
Enum, ViewerSetting
ViewerSetting -> ViewerSetting -> Bounded ViewerSetting
forall a. a -> a -> Bounded a
$cminBound :: ViewerSetting
minBound :: ViewerSetting
$cmaxBound :: ViewerSetting
maxBound :: ViewerSetting
Bounded)
data Numbering
= Unnumbered
| Numbered
| Modulo100
deriving (Numbering -> Numbering -> Bool
(Numbering -> Numbering -> Bool)
-> (Numbering -> Numbering -> Bool) -> Eq Numbering
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Numbering -> Numbering -> Bool
== :: Numbering -> Numbering -> Bool
$c/= :: Numbering -> Numbering -> Bool
/= :: Numbering -> Numbering -> Bool
Eq, Eq Numbering
Eq Numbering =>
(Numbering -> Numbering -> Ordering)
-> (Numbering -> Numbering -> Bool)
-> (Numbering -> Numbering -> Bool)
-> (Numbering -> Numbering -> Bool)
-> (Numbering -> Numbering -> Bool)
-> (Numbering -> Numbering -> Numbering)
-> (Numbering -> Numbering -> Numbering)
-> Ord Numbering
Numbering -> Numbering -> Bool
Numbering -> Numbering -> Ordering
Numbering -> Numbering -> Numbering
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Numbering -> Numbering -> Ordering
compare :: Numbering -> Numbering -> Ordering
$c< :: Numbering -> Numbering -> Bool
< :: Numbering -> Numbering -> Bool
$c<= :: Numbering -> Numbering -> Bool
<= :: Numbering -> Numbering -> Bool
$c> :: Numbering -> Numbering -> Bool
> :: Numbering -> Numbering -> Bool
$c>= :: Numbering -> Numbering -> Bool
>= :: Numbering -> Numbering -> Bool
$cmax :: Numbering -> Numbering -> Numbering
max :: Numbering -> Numbering -> Numbering
$cmin :: Numbering -> Numbering -> Numbering
min :: Numbering -> Numbering -> Numbering
Ord, Int -> Numbering -> ShowS
[Numbering] -> ShowS
Numbering -> String
(Int -> Numbering -> ShowS)
-> (Numbering -> String)
-> ([Numbering] -> ShowS)
-> Show Numbering
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Numbering -> ShowS
showsPrec :: Int -> Numbering -> ShowS
$cshow :: Numbering -> String
show :: Numbering -> String
$cshowList :: [Numbering] -> ShowS
showList :: [Numbering] -> ShowS
Show, ReadPrec [Numbering]
ReadPrec Numbering
Int -> ReadS Numbering
ReadS [Numbering]
(Int -> ReadS Numbering)
-> ReadS [Numbering]
-> ReadPrec Numbering
-> ReadPrec [Numbering]
-> Read Numbering
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Numbering
readsPrec :: Int -> ReadS Numbering
$creadList :: ReadS [Numbering]
readList :: ReadS [Numbering]
$creadPrec :: ReadPrec Numbering
readPrec :: ReadPrec Numbering
$creadListPrec :: ReadPrec [Numbering]
readListPrec :: ReadPrec [Numbering]
Read, Int -> Numbering
Numbering -> Int
Numbering -> [Numbering]
Numbering -> Numbering
Numbering -> Numbering -> [Numbering]
Numbering -> Numbering -> Numbering -> [Numbering]
(Numbering -> Numbering)
-> (Numbering -> Numbering)
-> (Int -> Numbering)
-> (Numbering -> Int)
-> (Numbering -> [Numbering])
-> (Numbering -> Numbering -> [Numbering])
-> (Numbering -> Numbering -> [Numbering])
-> (Numbering -> Numbering -> Numbering -> [Numbering])
-> Enum Numbering
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Numbering -> Numbering
succ :: Numbering -> Numbering
$cpred :: Numbering -> Numbering
pred :: Numbering -> Numbering
$ctoEnum :: Int -> Numbering
toEnum :: Int -> Numbering
$cfromEnum :: Numbering -> Int
fromEnum :: Numbering -> Int
$cenumFrom :: Numbering -> [Numbering]
enumFrom :: Numbering -> [Numbering]
$cenumFromThen :: Numbering -> Numbering -> [Numbering]
enumFromThen :: Numbering -> Numbering -> [Numbering]
$cenumFromTo :: Numbering -> Numbering -> [Numbering]
enumFromTo :: Numbering -> Numbering -> [Numbering]
$cenumFromThenTo :: Numbering -> Numbering -> Numbering -> [Numbering]
enumFromThenTo :: Numbering -> Numbering -> Numbering -> [Numbering]
Enum, Numbering
Numbering -> Numbering -> Bounded Numbering
forall a. a -> a -> Bounded a
$cminBound :: Numbering
minBound :: Numbering
$cmaxBound :: Numbering
maxBound :: Numbering
Bounded)
allGameInfoTypes :: [GameInfoType]
allGameInfoTypes = [Color -> GameInfoType
TeamName Color
Black, Color -> GameInfoType
TeamName Color
White, Color -> GameInfoType
PlayerName Color
Black, Color -> GameInfoType
PlayerName Color
White, GameInfoType
Annotator, GameInfoType
Source, GameInfoType
User, GameInfoType
Copyright, GameInfoType
Context, GameInfoType
Location, GameInfoType
Event, GameInfoType
GameName, GameInfoType
Opening, GameInfoType
Overtime]
instance Enum GameInfoType where
toEnum :: Int -> GameInfoType
toEnum = ([GameInfoType]
allGameInfoTypes [GameInfoType] -> Int -> GameInfoType
forall a. HasCallStack => [a] -> Int -> a
!!)
fromEnum :: GameInfoType -> Int
fromEnum GameInfoType
t = Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (GameInfoType -> Bool) -> [GameInfoType] -> Maybe Int
forall a. (a -> Bool) -> [a] -> Maybe Int
findIndex (GameInfoType
tGameInfoType -> GameInfoType -> Bool
forall a. Eq a => a -> a -> Bool
==) [GameInfoType]
allGameInfoTypes
instance Bounded GameInfoType where
minBound :: GameInfoType
minBound = [GameInfoType] -> GameInfoType
forall a. HasCallStack => [a] -> a
head [GameInfoType]
allGameInfoTypes
maxBound :: GameInfoType
maxBound = [GameInfoType] -> GameInfoType
forall a. HasCallStack => [a] -> a
last [GameInfoType]
allGameInfoTypes
data RuleSetGo
= AGA
| GOE
| Chinese | Japanese | NewZealand
deriving (RuleSetGo -> RuleSetGo -> Bool
(RuleSetGo -> RuleSetGo -> Bool)
-> (RuleSetGo -> RuleSetGo -> Bool) -> Eq RuleSetGo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RuleSetGo -> RuleSetGo -> Bool
== :: RuleSetGo -> RuleSetGo -> Bool
$c/= :: RuleSetGo -> RuleSetGo -> Bool
/= :: RuleSetGo -> RuleSetGo -> Bool
Eq, Eq RuleSetGo
Eq RuleSetGo =>
(RuleSetGo -> RuleSetGo -> Ordering)
-> (RuleSetGo -> RuleSetGo -> Bool)
-> (RuleSetGo -> RuleSetGo -> Bool)
-> (RuleSetGo -> RuleSetGo -> Bool)
-> (RuleSetGo -> RuleSetGo -> Bool)
-> (RuleSetGo -> RuleSetGo -> RuleSetGo)
-> (RuleSetGo -> RuleSetGo -> RuleSetGo)
-> Ord RuleSetGo
RuleSetGo -> RuleSetGo -> Bool
RuleSetGo -> RuleSetGo -> Ordering
RuleSetGo -> RuleSetGo -> RuleSetGo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RuleSetGo -> RuleSetGo -> Ordering
compare :: RuleSetGo -> RuleSetGo -> Ordering
$c< :: RuleSetGo -> RuleSetGo -> Bool
< :: RuleSetGo -> RuleSetGo -> Bool
$c<= :: RuleSetGo -> RuleSetGo -> Bool
<= :: RuleSetGo -> RuleSetGo -> Bool
$c> :: RuleSetGo -> RuleSetGo -> Bool
> :: RuleSetGo -> RuleSetGo -> Bool
$c>= :: RuleSetGo -> RuleSetGo -> Bool
>= :: RuleSetGo -> RuleSetGo -> Bool
$cmax :: RuleSetGo -> RuleSetGo -> RuleSetGo
max :: RuleSetGo -> RuleSetGo -> RuleSetGo
$cmin :: RuleSetGo -> RuleSetGo -> RuleSetGo
min :: RuleSetGo -> RuleSetGo -> RuleSetGo
Ord, Int -> RuleSetGo -> ShowS
[RuleSetGo] -> ShowS
RuleSetGo -> String
(Int -> RuleSetGo -> ShowS)
-> (RuleSetGo -> String)
-> ([RuleSetGo] -> ShowS)
-> Show RuleSetGo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RuleSetGo -> ShowS
showsPrec :: Int -> RuleSetGo -> ShowS
$cshow :: RuleSetGo -> String
show :: RuleSetGo -> String
$cshowList :: [RuleSetGo] -> ShowS
showList :: [RuleSetGo] -> ShowS
Show, ReadPrec [RuleSetGo]
ReadPrec RuleSetGo
Int -> ReadS RuleSetGo
ReadS [RuleSetGo]
(Int -> ReadS RuleSetGo)
-> ReadS [RuleSetGo]
-> ReadPrec RuleSetGo
-> ReadPrec [RuleSetGo]
-> Read RuleSetGo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RuleSetGo
readsPrec :: Int -> ReadS RuleSetGo
$creadList :: ReadS [RuleSetGo]
readList :: ReadS [RuleSetGo]
$creadPrec :: ReadPrec RuleSetGo
readPrec :: ReadPrec RuleSetGo
$creadListPrec :: ReadPrec [RuleSetGo]
readListPrec :: ReadPrec [RuleSetGo]
Read, Int -> RuleSetGo
RuleSetGo -> Int
RuleSetGo -> [RuleSetGo]
RuleSetGo -> RuleSetGo
RuleSetGo -> RuleSetGo -> [RuleSetGo]
RuleSetGo -> RuleSetGo -> RuleSetGo -> [RuleSetGo]
(RuleSetGo -> RuleSetGo)
-> (RuleSetGo -> RuleSetGo)
-> (Int -> RuleSetGo)
-> (RuleSetGo -> Int)
-> (RuleSetGo -> [RuleSetGo])
-> (RuleSetGo -> RuleSetGo -> [RuleSetGo])
-> (RuleSetGo -> RuleSetGo -> [RuleSetGo])
-> (RuleSetGo -> RuleSetGo -> RuleSetGo -> [RuleSetGo])
-> Enum RuleSetGo
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RuleSetGo -> RuleSetGo
succ :: RuleSetGo -> RuleSetGo
$cpred :: RuleSetGo -> RuleSetGo
pred :: RuleSetGo -> RuleSetGo
$ctoEnum :: Int -> RuleSetGo
toEnum :: Int -> RuleSetGo
$cfromEnum :: RuleSetGo -> Int
fromEnum :: RuleSetGo -> Int
$cenumFrom :: RuleSetGo -> [RuleSetGo]
enumFrom :: RuleSetGo -> [RuleSetGo]
$cenumFromThen :: RuleSetGo -> RuleSetGo -> [RuleSetGo]
enumFromThen :: RuleSetGo -> RuleSetGo -> [RuleSetGo]
$cenumFromTo :: RuleSetGo -> RuleSetGo -> [RuleSetGo]
enumFromTo :: RuleSetGo -> RuleSetGo -> [RuleSetGo]
$cenumFromThenTo :: RuleSetGo -> RuleSetGo -> RuleSetGo -> [RuleSetGo]
enumFromThenTo :: RuleSetGo -> RuleSetGo -> RuleSetGo -> [RuleSetGo]
Enum, RuleSetGo
RuleSetGo -> RuleSetGo -> Bounded RuleSetGo
forall a. a -> a -> Bounded a
$cminBound :: RuleSetGo
minBound :: RuleSetGo
$cmaxBound :: RuleSetGo
maxBound :: RuleSetGo
Bounded)
data RuleSetBackgammon
= Crawford
| CrawfordGame
| Jacoby
deriving (RuleSetBackgammon -> RuleSetBackgammon -> Bool
(RuleSetBackgammon -> RuleSetBackgammon -> Bool)
-> (RuleSetBackgammon -> RuleSetBackgammon -> Bool)
-> Eq RuleSetBackgammon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
== :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
$c/= :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
/= :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
Eq, Eq RuleSetBackgammon
Eq RuleSetBackgammon =>
(RuleSetBackgammon -> RuleSetBackgammon -> Ordering)
-> (RuleSetBackgammon -> RuleSetBackgammon -> Bool)
-> (RuleSetBackgammon -> RuleSetBackgammon -> Bool)
-> (RuleSetBackgammon -> RuleSetBackgammon -> Bool)
-> (RuleSetBackgammon -> RuleSetBackgammon -> Bool)
-> (RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon)
-> (RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon)
-> Ord RuleSetBackgammon
RuleSetBackgammon -> RuleSetBackgammon -> Bool
RuleSetBackgammon -> RuleSetBackgammon -> Ordering
RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RuleSetBackgammon -> RuleSetBackgammon -> Ordering
compare :: RuleSetBackgammon -> RuleSetBackgammon -> Ordering
$c< :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
< :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
$c<= :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
<= :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
$c> :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
> :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
$c>= :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
>= :: RuleSetBackgammon -> RuleSetBackgammon -> Bool
$cmax :: RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon
max :: RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon
$cmin :: RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon
min :: RuleSetBackgammon -> RuleSetBackgammon -> RuleSetBackgammon
Ord, Int -> RuleSetBackgammon -> ShowS
[RuleSetBackgammon] -> ShowS
RuleSetBackgammon -> String
(Int -> RuleSetBackgammon -> ShowS)
-> (RuleSetBackgammon -> String)
-> ([RuleSetBackgammon] -> ShowS)
-> Show RuleSetBackgammon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RuleSetBackgammon -> ShowS
showsPrec :: Int -> RuleSetBackgammon -> ShowS
$cshow :: RuleSetBackgammon -> String
show :: RuleSetBackgammon -> String
$cshowList :: [RuleSetBackgammon] -> ShowS
showList :: [RuleSetBackgammon] -> ShowS
Show, ReadPrec [RuleSetBackgammon]
ReadPrec RuleSetBackgammon
Int -> ReadS RuleSetBackgammon
ReadS [RuleSetBackgammon]
(Int -> ReadS RuleSetBackgammon)
-> ReadS [RuleSetBackgammon]
-> ReadPrec RuleSetBackgammon
-> ReadPrec [RuleSetBackgammon]
-> Read RuleSetBackgammon
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RuleSetBackgammon
readsPrec :: Int -> ReadS RuleSetBackgammon
$creadList :: ReadS [RuleSetBackgammon]
readList :: ReadS [RuleSetBackgammon]
$creadPrec :: ReadPrec RuleSetBackgammon
readPrec :: ReadPrec RuleSetBackgammon
$creadListPrec :: ReadPrec [RuleSetBackgammon]
readListPrec :: ReadPrec [RuleSetBackgammon]
Read, Int -> RuleSetBackgammon
RuleSetBackgammon -> Int
RuleSetBackgammon -> [RuleSetBackgammon]
RuleSetBackgammon -> RuleSetBackgammon
RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
RuleSetBackgammon
-> RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
(RuleSetBackgammon -> RuleSetBackgammon)
-> (RuleSetBackgammon -> RuleSetBackgammon)
-> (Int -> RuleSetBackgammon)
-> (RuleSetBackgammon -> Int)
-> (RuleSetBackgammon -> [RuleSetBackgammon])
-> (RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon])
-> (RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon])
-> (RuleSetBackgammon
-> RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon])
-> Enum RuleSetBackgammon
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RuleSetBackgammon -> RuleSetBackgammon
succ :: RuleSetBackgammon -> RuleSetBackgammon
$cpred :: RuleSetBackgammon -> RuleSetBackgammon
pred :: RuleSetBackgammon -> RuleSetBackgammon
$ctoEnum :: Int -> RuleSetBackgammon
toEnum :: Int -> RuleSetBackgammon
$cfromEnum :: RuleSetBackgammon -> Int
fromEnum :: RuleSetBackgammon -> Int
$cenumFrom :: RuleSetBackgammon -> [RuleSetBackgammon]
enumFrom :: RuleSetBackgammon -> [RuleSetBackgammon]
$cenumFromThen :: RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
enumFromThen :: RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
$cenumFromTo :: RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
enumFromTo :: RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
$cenumFromThenTo :: RuleSetBackgammon
-> RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
enumFromThenTo :: RuleSetBackgammon
-> RuleSetBackgammon -> RuleSetBackgammon -> [RuleSetBackgammon]
Enum, RuleSetBackgammon
RuleSetBackgammon -> RuleSetBackgammon -> Bounded RuleSetBackgammon
forall a. a -> a -> Bounded a
$cminBound :: RuleSetBackgammon
minBound :: RuleSetBackgammon
$cmaxBound :: RuleSetBackgammon
maxBound :: RuleSetBackgammon
Bounded)
data RuleSetOcti = OctiRuleSet MajorVariation (Set MinorVariation) deriving (RuleSetOcti -> RuleSetOcti -> Bool
(RuleSetOcti -> RuleSetOcti -> Bool)
-> (RuleSetOcti -> RuleSetOcti -> Bool) -> Eq RuleSetOcti
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RuleSetOcti -> RuleSetOcti -> Bool
== :: RuleSetOcti -> RuleSetOcti -> Bool
$c/= :: RuleSetOcti -> RuleSetOcti -> Bool
/= :: RuleSetOcti -> RuleSetOcti -> Bool
Eq, Eq RuleSetOcti
Eq RuleSetOcti =>
(RuleSetOcti -> RuleSetOcti -> Ordering)
-> (RuleSetOcti -> RuleSetOcti -> Bool)
-> (RuleSetOcti -> RuleSetOcti -> Bool)
-> (RuleSetOcti -> RuleSetOcti -> Bool)
-> (RuleSetOcti -> RuleSetOcti -> Bool)
-> (RuleSetOcti -> RuleSetOcti -> RuleSetOcti)
-> (RuleSetOcti -> RuleSetOcti -> RuleSetOcti)
-> Ord RuleSetOcti
RuleSetOcti -> RuleSetOcti -> Bool
RuleSetOcti -> RuleSetOcti -> Ordering
RuleSetOcti -> RuleSetOcti -> RuleSetOcti
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RuleSetOcti -> RuleSetOcti -> Ordering
compare :: RuleSetOcti -> RuleSetOcti -> Ordering
$c< :: RuleSetOcti -> RuleSetOcti -> Bool
< :: RuleSetOcti -> RuleSetOcti -> Bool
$c<= :: RuleSetOcti -> RuleSetOcti -> Bool
<= :: RuleSetOcti -> RuleSetOcti -> Bool
$c> :: RuleSetOcti -> RuleSetOcti -> Bool
> :: RuleSetOcti -> RuleSetOcti -> Bool
$c>= :: RuleSetOcti -> RuleSetOcti -> Bool
>= :: RuleSetOcti -> RuleSetOcti -> Bool
$cmax :: RuleSetOcti -> RuleSetOcti -> RuleSetOcti
max :: RuleSetOcti -> RuleSetOcti -> RuleSetOcti
$cmin :: RuleSetOcti -> RuleSetOcti -> RuleSetOcti
min :: RuleSetOcti -> RuleSetOcti -> RuleSetOcti
Ord, Int -> RuleSetOcti -> ShowS
[RuleSetOcti] -> ShowS
RuleSetOcti -> String
(Int -> RuleSetOcti -> ShowS)
-> (RuleSetOcti -> String)
-> ([RuleSetOcti] -> ShowS)
-> Show RuleSetOcti
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RuleSetOcti -> ShowS
showsPrec :: Int -> RuleSetOcti -> ShowS
$cshow :: RuleSetOcti -> String
show :: RuleSetOcti -> String
$cshowList :: [RuleSetOcti] -> ShowS
showList :: [RuleSetOcti] -> ShowS
Show, ReadPrec [RuleSetOcti]
ReadPrec RuleSetOcti
Int -> ReadS RuleSetOcti
ReadS [RuleSetOcti]
(Int -> ReadS RuleSetOcti)
-> ReadS [RuleSetOcti]
-> ReadPrec RuleSetOcti
-> ReadPrec [RuleSetOcti]
-> Read RuleSetOcti
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RuleSetOcti
readsPrec :: Int -> ReadS RuleSetOcti
$creadList :: ReadS [RuleSetOcti]
readList :: ReadS [RuleSetOcti]
$creadPrec :: ReadPrec RuleSetOcti
readPrec :: ReadPrec RuleSetOcti
$creadListPrec :: ReadPrec [RuleSetOcti]
readListPrec :: ReadPrec [RuleSetOcti]
Read)
data MajorVariation = Full | Fast | Kids deriving (MajorVariation -> MajorVariation -> Bool
(MajorVariation -> MajorVariation -> Bool)
-> (MajorVariation -> MajorVariation -> Bool) -> Eq MajorVariation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MajorVariation -> MajorVariation -> Bool
== :: MajorVariation -> MajorVariation -> Bool
$c/= :: MajorVariation -> MajorVariation -> Bool
/= :: MajorVariation -> MajorVariation -> Bool
Eq, Eq MajorVariation
Eq MajorVariation =>
(MajorVariation -> MajorVariation -> Ordering)
-> (MajorVariation -> MajorVariation -> Bool)
-> (MajorVariation -> MajorVariation -> Bool)
-> (MajorVariation -> MajorVariation -> Bool)
-> (MajorVariation -> MajorVariation -> Bool)
-> (MajorVariation -> MajorVariation -> MajorVariation)
-> (MajorVariation -> MajorVariation -> MajorVariation)
-> Ord MajorVariation
MajorVariation -> MajorVariation -> Bool
MajorVariation -> MajorVariation -> Ordering
MajorVariation -> MajorVariation -> MajorVariation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MajorVariation -> MajorVariation -> Ordering
compare :: MajorVariation -> MajorVariation -> Ordering
$c< :: MajorVariation -> MajorVariation -> Bool
< :: MajorVariation -> MajorVariation -> Bool
$c<= :: MajorVariation -> MajorVariation -> Bool
<= :: MajorVariation -> MajorVariation -> Bool
$c> :: MajorVariation -> MajorVariation -> Bool
> :: MajorVariation -> MajorVariation -> Bool
$c>= :: MajorVariation -> MajorVariation -> Bool
>= :: MajorVariation -> MajorVariation -> Bool
$cmax :: MajorVariation -> MajorVariation -> MajorVariation
max :: MajorVariation -> MajorVariation -> MajorVariation
$cmin :: MajorVariation -> MajorVariation -> MajorVariation
min :: MajorVariation -> MajorVariation -> MajorVariation
Ord, Int -> MajorVariation -> ShowS
[MajorVariation] -> ShowS
MajorVariation -> String
(Int -> MajorVariation -> ShowS)
-> (MajorVariation -> String)
-> ([MajorVariation] -> ShowS)
-> Show MajorVariation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MajorVariation -> ShowS
showsPrec :: Int -> MajorVariation -> ShowS
$cshow :: MajorVariation -> String
show :: MajorVariation -> String
$cshowList :: [MajorVariation] -> ShowS
showList :: [MajorVariation] -> ShowS
Show, ReadPrec [MajorVariation]
ReadPrec MajorVariation
Int -> ReadS MajorVariation
ReadS [MajorVariation]
(Int -> ReadS MajorVariation)
-> ReadS [MajorVariation]
-> ReadPrec MajorVariation
-> ReadPrec [MajorVariation]
-> Read MajorVariation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MajorVariation
readsPrec :: Int -> ReadS MajorVariation
$creadList :: ReadS [MajorVariation]
readList :: ReadS [MajorVariation]
$creadPrec :: ReadPrec MajorVariation
readPrec :: ReadPrec MajorVariation
$creadListPrec :: ReadPrec [MajorVariation]
readListPrec :: ReadPrec [MajorVariation]
Read, Int -> MajorVariation
MajorVariation -> Int
MajorVariation -> [MajorVariation]
MajorVariation -> MajorVariation
MajorVariation -> MajorVariation -> [MajorVariation]
MajorVariation
-> MajorVariation -> MajorVariation -> [MajorVariation]
(MajorVariation -> MajorVariation)
-> (MajorVariation -> MajorVariation)
-> (Int -> MajorVariation)
-> (MajorVariation -> Int)
-> (MajorVariation -> [MajorVariation])
-> (MajorVariation -> MajorVariation -> [MajorVariation])
-> (MajorVariation -> MajorVariation -> [MajorVariation])
-> (MajorVariation
-> MajorVariation -> MajorVariation -> [MajorVariation])
-> Enum MajorVariation
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: MajorVariation -> MajorVariation
succ :: MajorVariation -> MajorVariation
$cpred :: MajorVariation -> MajorVariation
pred :: MajorVariation -> MajorVariation
$ctoEnum :: Int -> MajorVariation
toEnum :: Int -> MajorVariation
$cfromEnum :: MajorVariation -> Int
fromEnum :: MajorVariation -> Int
$cenumFrom :: MajorVariation -> [MajorVariation]
enumFrom :: MajorVariation -> [MajorVariation]
$cenumFromThen :: MajorVariation -> MajorVariation -> [MajorVariation]
enumFromThen :: MajorVariation -> MajorVariation -> [MajorVariation]
$cenumFromTo :: MajorVariation -> MajorVariation -> [MajorVariation]
enumFromTo :: MajorVariation -> MajorVariation -> [MajorVariation]
$cenumFromThenTo :: MajorVariation
-> MajorVariation -> MajorVariation -> [MajorVariation]
enumFromThenTo :: MajorVariation
-> MajorVariation -> MajorVariation -> [MajorVariation]
Enum, MajorVariation
MajorVariation -> MajorVariation -> Bounded MajorVariation
forall a. a -> a -> Bounded a
$cminBound :: MajorVariation
minBound :: MajorVariation
$cmaxBound :: MajorVariation
maxBound :: MajorVariation
Bounded)
data MinorVariation = Edgeless | Superprong | OtherMinorVariation String deriving (MinorVariation -> MinorVariation -> Bool
(MinorVariation -> MinorVariation -> Bool)
-> (MinorVariation -> MinorVariation -> Bool) -> Eq MinorVariation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MinorVariation -> MinorVariation -> Bool
== :: MinorVariation -> MinorVariation -> Bool
$c/= :: MinorVariation -> MinorVariation -> Bool
/= :: MinorVariation -> MinorVariation -> Bool
Eq, Eq MinorVariation
Eq MinorVariation =>
(MinorVariation -> MinorVariation -> Ordering)
-> (MinorVariation -> MinorVariation -> Bool)
-> (MinorVariation -> MinorVariation -> Bool)
-> (MinorVariation -> MinorVariation -> Bool)
-> (MinorVariation -> MinorVariation -> Bool)
-> (MinorVariation -> MinorVariation -> MinorVariation)
-> (MinorVariation -> MinorVariation -> MinorVariation)
-> Ord MinorVariation
MinorVariation -> MinorVariation -> Bool
MinorVariation -> MinorVariation -> Ordering
MinorVariation -> MinorVariation -> MinorVariation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MinorVariation -> MinorVariation -> Ordering
compare :: MinorVariation -> MinorVariation -> Ordering
$c< :: MinorVariation -> MinorVariation -> Bool
< :: MinorVariation -> MinorVariation -> Bool
$c<= :: MinorVariation -> MinorVariation -> Bool
<= :: MinorVariation -> MinorVariation -> Bool
$c> :: MinorVariation -> MinorVariation -> Bool
> :: MinorVariation -> MinorVariation -> Bool
$c>= :: MinorVariation -> MinorVariation -> Bool
>= :: MinorVariation -> MinorVariation -> Bool
$cmax :: MinorVariation -> MinorVariation -> MinorVariation
max :: MinorVariation -> MinorVariation -> MinorVariation
$cmin :: MinorVariation -> MinorVariation -> MinorVariation
min :: MinorVariation -> MinorVariation -> MinorVariation
Ord, Int -> MinorVariation -> ShowS
[MinorVariation] -> ShowS
MinorVariation -> String
(Int -> MinorVariation -> ShowS)
-> (MinorVariation -> String)
-> ([MinorVariation] -> ShowS)
-> Show MinorVariation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MinorVariation -> ShowS
showsPrec :: Int -> MinorVariation -> ShowS
$cshow :: MinorVariation -> String
show :: MinorVariation -> String
$cshowList :: [MinorVariation] -> ShowS
showList :: [MinorVariation] -> ShowS
Show, ReadPrec [MinorVariation]
ReadPrec MinorVariation
Int -> ReadS MinorVariation
ReadS [MinorVariation]
(Int -> ReadS MinorVariation)
-> ReadS [MinorVariation]
-> ReadPrec MinorVariation
-> ReadPrec [MinorVariation]
-> Read MinorVariation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MinorVariation
readsPrec :: Int -> ReadS MinorVariation
$creadList :: ReadS [MinorVariation]
readList :: ReadS [MinorVariation]
$creadPrec :: ReadPrec MinorVariation
readPrec :: ReadPrec MinorVariation
$creadListPrec :: ReadPrec [MinorVariation]
readListPrec :: ReadPrec [MinorVariation]
Read)
data RuleSet a = Known !a | OtherRuleSet String deriving (RuleSet a -> RuleSet a -> Bool
(RuleSet a -> RuleSet a -> Bool)
-> (RuleSet a -> RuleSet a -> Bool) -> Eq (RuleSet a)
forall a. Eq a => RuleSet a -> RuleSet a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => RuleSet a -> RuleSet a -> Bool
== :: RuleSet a -> RuleSet a -> Bool
$c/= :: forall a. Eq a => RuleSet a -> RuleSet a -> Bool
/= :: RuleSet a -> RuleSet a -> Bool
Eq, Eq (RuleSet a)
Eq (RuleSet a) =>
(RuleSet a -> RuleSet a -> Ordering)
-> (RuleSet a -> RuleSet a -> Bool)
-> (RuleSet a -> RuleSet a -> Bool)
-> (RuleSet a -> RuleSet a -> Bool)
-> (RuleSet a -> RuleSet a -> Bool)
-> (RuleSet a -> RuleSet a -> RuleSet a)
-> (RuleSet a -> RuleSet a -> RuleSet a)
-> Ord (RuleSet a)
RuleSet a -> RuleSet a -> Bool
RuleSet a -> RuleSet a -> Ordering
RuleSet a -> RuleSet a -> RuleSet a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (RuleSet a)
forall a. Ord a => RuleSet a -> RuleSet a -> Bool
forall a. Ord a => RuleSet a -> RuleSet a -> Ordering
forall a. Ord a => RuleSet a -> RuleSet a -> RuleSet a
$ccompare :: forall a. Ord a => RuleSet a -> RuleSet a -> Ordering
compare :: RuleSet a -> RuleSet a -> Ordering
$c< :: forall a. Ord a => RuleSet a -> RuleSet a -> Bool
< :: RuleSet a -> RuleSet a -> Bool
$c<= :: forall a. Ord a => RuleSet a -> RuleSet a -> Bool
<= :: RuleSet a -> RuleSet a -> Bool
$c> :: forall a. Ord a => RuleSet a -> RuleSet a -> Bool
> :: RuleSet a -> RuleSet a -> Bool
$c>= :: forall a. Ord a => RuleSet a -> RuleSet a -> Bool
>= :: RuleSet a -> RuleSet a -> Bool
$cmax :: forall a. Ord a => RuleSet a -> RuleSet a -> RuleSet a
max :: RuleSet a -> RuleSet a -> RuleSet a
$cmin :: forall a. Ord a => RuleSet a -> RuleSet a -> RuleSet a
min :: RuleSet a -> RuleSet a -> RuleSet a
Ord, Int -> RuleSet a -> ShowS
[RuleSet a] -> ShowS
RuleSet a -> String
(Int -> RuleSet a -> ShowS)
-> (RuleSet a -> String)
-> ([RuleSet a] -> ShowS)
-> Show (RuleSet a)
forall a. Show a => Int -> RuleSet a -> ShowS
forall a. Show a => [RuleSet a] -> ShowS
forall a. Show a => RuleSet a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> RuleSet a -> ShowS
showsPrec :: Int -> RuleSet a -> ShowS
$cshow :: forall a. Show a => RuleSet a -> String
show :: RuleSet a -> String
$cshowList :: forall a. Show a => [RuleSet a] -> ShowS
showList :: [RuleSet a] -> ShowS
Show, ReadPrec [RuleSet a]
ReadPrec (RuleSet a)
Int -> ReadS (RuleSet a)
ReadS [RuleSet a]
(Int -> ReadS (RuleSet a))
-> ReadS [RuleSet a]
-> ReadPrec (RuleSet a)
-> ReadPrec [RuleSet a]
-> Read (RuleSet a)
forall a. Read a => ReadPrec [RuleSet a]
forall a. Read a => ReadPrec (RuleSet a)
forall a. Read a => Int -> ReadS (RuleSet a)
forall a. Read a => ReadS [RuleSet a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (RuleSet a)
readsPrec :: Int -> ReadS (RuleSet a)
$creadList :: forall a. Read a => ReadS [RuleSet a]
readList :: ReadS [RuleSet a]
$creadPrec :: forall a. Read a => ReadPrec (RuleSet a)
readPrec :: ReadPrec (RuleSet a)
$creadListPrec :: forall a. Read a => ReadPrec [RuleSet a]
readListPrec :: ReadPrec [RuleSet a]
Read)
data WinType = Score Rational | Resign | Time | Forfeit | OtherWinType deriving (WinType -> WinType -> Bool
(WinType -> WinType -> Bool)
-> (WinType -> WinType -> Bool) -> Eq WinType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WinType -> WinType -> Bool
== :: WinType -> WinType -> Bool
$c/= :: WinType -> WinType -> Bool
/= :: WinType -> WinType -> Bool
Eq, Eq WinType
Eq WinType =>
(WinType -> WinType -> Ordering)
-> (WinType -> WinType -> Bool)
-> (WinType -> WinType -> Bool)
-> (WinType -> WinType -> Bool)
-> (WinType -> WinType -> Bool)
-> (WinType -> WinType -> WinType)
-> (WinType -> WinType -> WinType)
-> Ord WinType
WinType -> WinType -> Bool
WinType -> WinType -> Ordering
WinType -> WinType -> WinType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WinType -> WinType -> Ordering
compare :: WinType -> WinType -> Ordering
$c< :: WinType -> WinType -> Bool
< :: WinType -> WinType -> Bool
$c<= :: WinType -> WinType -> Bool
<= :: WinType -> WinType -> Bool
$c> :: WinType -> WinType -> Bool
> :: WinType -> WinType -> Bool
$c>= :: WinType -> WinType -> Bool
>= :: WinType -> WinType -> Bool
$cmax :: WinType -> WinType -> WinType
max :: WinType -> WinType -> WinType
$cmin :: WinType -> WinType -> WinType
min :: WinType -> WinType -> WinType
Ord, Int -> WinType -> ShowS
[WinType] -> ShowS
WinType -> String
(Int -> WinType -> ShowS)
-> (WinType -> String) -> ([WinType] -> ShowS) -> Show WinType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WinType -> ShowS
showsPrec :: Int -> WinType -> ShowS
$cshow :: WinType -> String
show :: WinType -> String
$cshowList :: [WinType] -> ShowS
showList :: [WinType] -> ShowS
Show, ReadPrec [WinType]
ReadPrec WinType
Int -> ReadS WinType
ReadS [WinType]
(Int -> ReadS WinType)
-> ReadS [WinType]
-> ReadPrec WinType
-> ReadPrec [WinType]
-> Read WinType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS WinType
readsPrec :: Int -> ReadS WinType
$creadList :: ReadS [WinType]
readList :: ReadS [WinType]
$creadPrec :: ReadPrec WinType
readPrec :: ReadPrec WinType
$creadListPrec :: ReadPrec [WinType]
readListPrec :: ReadPrec [WinType]
Read)
data Quality = Bad Emphasis | Doubtful | Interesting | Good Emphasis deriving (Quality -> Quality -> Bool
(Quality -> Quality -> Bool)
-> (Quality -> Quality -> Bool) -> Eq Quality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Quality -> Quality -> Bool
== :: Quality -> Quality -> Bool
$c/= :: Quality -> Quality -> Bool
/= :: Quality -> Quality -> Bool
Eq, Eq Quality
Eq Quality =>
(Quality -> Quality -> Ordering)
-> (Quality -> Quality -> Bool)
-> (Quality -> Quality -> Bool)
-> (Quality -> Quality -> Bool)
-> (Quality -> Quality -> Bool)
-> (Quality -> Quality -> Quality)
-> (Quality -> Quality -> Quality)
-> Ord Quality
Quality -> Quality -> Bool
Quality -> Quality -> Ordering
Quality -> Quality -> Quality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Quality -> Quality -> Ordering
compare :: Quality -> Quality -> Ordering
$c< :: Quality -> Quality -> Bool
< :: Quality -> Quality -> Bool
$c<= :: Quality -> Quality -> Bool
<= :: Quality -> Quality -> Bool
$c> :: Quality -> Quality -> Bool
> :: Quality -> Quality -> Bool
$c>= :: Quality -> Quality -> Bool
>= :: Quality -> Quality -> Bool
$cmax :: Quality -> Quality -> Quality
max :: Quality -> Quality -> Quality
$cmin :: Quality -> Quality -> Quality
min :: Quality -> Quality -> Quality
Ord, Int -> Quality -> ShowS
[Quality] -> ShowS
Quality -> String
(Int -> Quality -> ShowS)
-> (Quality -> String) -> ([Quality] -> ShowS) -> Show Quality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Quality -> ShowS
showsPrec :: Int -> Quality -> ShowS
$cshow :: Quality -> String
show :: Quality -> String
$cshowList :: [Quality] -> ShowS
showList :: [Quality] -> ShowS
Show, ReadPrec [Quality]
ReadPrec Quality
Int -> ReadS Quality
ReadS [Quality]
(Int -> ReadS Quality)
-> ReadS [Quality]
-> ReadPrec Quality
-> ReadPrec [Quality]
-> Read Quality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Quality
readsPrec :: Int -> ReadS Quality
$creadList :: ReadS [Quality]
readList :: ReadS [Quality]
$creadPrec :: ReadPrec Quality
readPrec :: ReadPrec Quality
$creadListPrec :: ReadPrec [Quality]
readListPrec :: ReadPrec [Quality]
Read)
data GameResult
= Draw | Void | Unknown
| Win Color WinType
deriving (GameResult -> GameResult -> Bool
(GameResult -> GameResult -> Bool)
-> (GameResult -> GameResult -> Bool) -> Eq GameResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameResult -> GameResult -> Bool
== :: GameResult -> GameResult -> Bool
$c/= :: GameResult -> GameResult -> Bool
/= :: GameResult -> GameResult -> Bool
Eq, Eq GameResult
Eq GameResult =>
(GameResult -> GameResult -> Ordering)
-> (GameResult -> GameResult -> Bool)
-> (GameResult -> GameResult -> Bool)
-> (GameResult -> GameResult -> Bool)
-> (GameResult -> GameResult -> Bool)
-> (GameResult -> GameResult -> GameResult)
-> (GameResult -> GameResult -> GameResult)
-> Ord GameResult
GameResult -> GameResult -> Bool
GameResult -> GameResult -> Ordering
GameResult -> GameResult -> GameResult
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameResult -> GameResult -> Ordering
compare :: GameResult -> GameResult -> Ordering
$c< :: GameResult -> GameResult -> Bool
< :: GameResult -> GameResult -> Bool
$c<= :: GameResult -> GameResult -> Bool
<= :: GameResult -> GameResult -> Bool
$c> :: GameResult -> GameResult -> Bool
> :: GameResult -> GameResult -> Bool
$c>= :: GameResult -> GameResult -> Bool
>= :: GameResult -> GameResult -> Bool
$cmax :: GameResult -> GameResult -> GameResult
max :: GameResult -> GameResult -> GameResult
$cmin :: GameResult -> GameResult -> GameResult
min :: GameResult -> GameResult -> GameResult
Ord, Int -> GameResult -> ShowS
[GameResult] -> ShowS
GameResult -> String
(Int -> GameResult -> ShowS)
-> (GameResult -> String)
-> ([GameResult] -> ShowS)
-> Show GameResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameResult -> ShowS
showsPrec :: Int -> GameResult -> ShowS
$cshow :: GameResult -> String
show :: GameResult -> String
$cshowList :: [GameResult] -> ShowS
showList :: [GameResult] -> ShowS
Show, ReadPrec [GameResult]
ReadPrec GameResult
Int -> ReadS GameResult
ReadS [GameResult]
(Int -> ReadS GameResult)
-> ReadS [GameResult]
-> ReadPrec GameResult
-> ReadPrec [GameResult]
-> Read GameResult
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameResult
readsPrec :: Int -> ReadS GameResult
$creadList :: ReadS [GameResult]
readList :: ReadS [GameResult]
$creadPrec :: ReadPrec GameResult
readPrec :: ReadPrec GameResult
$creadListPrec :: ReadPrec [GameResult]
readListPrec :: ReadPrec [GameResult]
Read)
data Rank
= Ranked Integer RankScale (Maybe Certainty)
| OtherRank String
deriving (Rank -> Rank -> Bool
(Rank -> Rank -> Bool) -> (Rank -> Rank -> Bool) -> Eq Rank
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rank -> Rank -> Bool
== :: Rank -> Rank -> Bool
$c/= :: Rank -> Rank -> Bool
/= :: Rank -> Rank -> Bool
Eq, Eq Rank
Eq Rank =>
(Rank -> Rank -> Ordering)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Rank)
-> (Rank -> Rank -> Rank)
-> Ord Rank
Rank -> Rank -> Bool
Rank -> Rank -> Ordering
Rank -> Rank -> Rank
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Rank -> Rank -> Ordering
compare :: Rank -> Rank -> Ordering
$c< :: Rank -> Rank -> Bool
< :: Rank -> Rank -> Bool
$c<= :: Rank -> Rank -> Bool
<= :: Rank -> Rank -> Bool
$c> :: Rank -> Rank -> Bool
> :: Rank -> Rank -> Bool
$c>= :: Rank -> Rank -> Bool
>= :: Rank -> Rank -> Bool
$cmax :: Rank -> Rank -> Rank
max :: Rank -> Rank -> Rank
$cmin :: Rank -> Rank -> Rank
min :: Rank -> Rank -> Rank
Ord, Int -> Rank -> ShowS
[Rank] -> ShowS
Rank -> String
(Int -> Rank -> ShowS)
-> (Rank -> String) -> ([Rank] -> ShowS) -> Show Rank
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rank -> ShowS
showsPrec :: Int -> Rank -> ShowS
$cshow :: Rank -> String
show :: Rank -> String
$cshowList :: [Rank] -> ShowS
showList :: [Rank] -> ShowS
Show, ReadPrec [Rank]
ReadPrec Rank
Int -> ReadS Rank
ReadS [Rank]
(Int -> ReadS Rank)
-> ReadS [Rank] -> ReadPrec Rank -> ReadPrec [Rank] -> Read Rank
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Rank
readsPrec :: Int -> ReadS Rank
$creadList :: ReadS [Rank]
readList :: ReadS [Rank]
$creadPrec :: ReadPrec Rank
readPrec :: ReadPrec Rank
$creadListPrec :: ReadPrec [Rank]
readListPrec :: ReadPrec [Rank]
Read)
data Round
= SimpleRound Integer
| FormattedRound Integer String
| OtherRound String
deriving (Round -> Round -> Bool
(Round -> Round -> Bool) -> (Round -> Round -> Bool) -> Eq Round
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Round -> Round -> Bool
== :: Round -> Round -> Bool
$c/= :: Round -> Round -> Bool
/= :: Round -> Round -> Bool
Eq, Eq Round
Eq Round =>
(Round -> Round -> Ordering)
-> (Round -> Round -> Bool)
-> (Round -> Round -> Bool)
-> (Round -> Round -> Bool)
-> (Round -> Round -> Bool)
-> (Round -> Round -> Round)
-> (Round -> Round -> Round)
-> Ord Round
Round -> Round -> Bool
Round -> Round -> Ordering
Round -> Round -> Round
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Round -> Round -> Ordering
compare :: Round -> Round -> Ordering
$c< :: Round -> Round -> Bool
< :: Round -> Round -> Bool
$c<= :: Round -> Round -> Bool
<= :: Round -> Round -> Bool
$c> :: Round -> Round -> Bool
> :: Round -> Round -> Bool
$c>= :: Round -> Round -> Bool
>= :: Round -> Round -> Bool
$cmax :: Round -> Round -> Round
max :: Round -> Round -> Round
$cmin :: Round -> Round -> Round
min :: Round -> Round -> Round
Ord, Int -> Round -> ShowS
[Round] -> ShowS
Round -> String
(Int -> Round -> ShowS)
-> (Round -> String) -> ([Round] -> ShowS) -> Show Round
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Round -> ShowS
showsPrec :: Int -> Round -> ShowS
$cshow :: Round -> String
show :: Round -> String
$cshowList :: [Round] -> ShowS
showList :: [Round] -> ShowS
Show, ReadPrec [Round]
ReadPrec Round
Int -> ReadS Round
ReadS [Round]
(Int -> ReadS Round)
-> ReadS [Round]
-> ReadPrec Round
-> ReadPrec [Round]
-> Read Round
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Round
readsPrec :: Int -> ReadS Round
$creadList :: ReadS [Round]
readList :: ReadS [Round]
$creadPrec :: ReadPrec Round
readPrec :: ReadPrec Round
$creadListPrec :: ReadPrec [Round]
readListPrec :: ReadPrec [Round]
Read)
data MatchInfo
= Length Integer
| Integer
| StartScore Color Integer
| OtherMatchInfo String String
deriving (MatchInfo -> MatchInfo -> Bool
(MatchInfo -> MatchInfo -> Bool)
-> (MatchInfo -> MatchInfo -> Bool) -> Eq MatchInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MatchInfo -> MatchInfo -> Bool
== :: MatchInfo -> MatchInfo -> Bool
$c/= :: MatchInfo -> MatchInfo -> Bool
/= :: MatchInfo -> MatchInfo -> Bool
Eq, Eq MatchInfo
Eq MatchInfo =>
(MatchInfo -> MatchInfo -> Ordering)
-> (MatchInfo -> MatchInfo -> Bool)
-> (MatchInfo -> MatchInfo -> Bool)
-> (MatchInfo -> MatchInfo -> Bool)
-> (MatchInfo -> MatchInfo -> Bool)
-> (MatchInfo -> MatchInfo -> MatchInfo)
-> (MatchInfo -> MatchInfo -> MatchInfo)
-> Ord MatchInfo
MatchInfo -> MatchInfo -> Bool
MatchInfo -> MatchInfo -> Ordering
MatchInfo -> MatchInfo -> MatchInfo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MatchInfo -> MatchInfo -> Ordering
compare :: MatchInfo -> MatchInfo -> Ordering
$c< :: MatchInfo -> MatchInfo -> Bool
< :: MatchInfo -> MatchInfo -> Bool
$c<= :: MatchInfo -> MatchInfo -> Bool
<= :: MatchInfo -> MatchInfo -> Bool
$c> :: MatchInfo -> MatchInfo -> Bool
> :: MatchInfo -> MatchInfo -> Bool
$c>= :: MatchInfo -> MatchInfo -> Bool
>= :: MatchInfo -> MatchInfo -> Bool
$cmax :: MatchInfo -> MatchInfo -> MatchInfo
max :: MatchInfo -> MatchInfo -> MatchInfo
$cmin :: MatchInfo -> MatchInfo -> MatchInfo
min :: MatchInfo -> MatchInfo -> MatchInfo
Ord, Int -> MatchInfo -> ShowS
[MatchInfo] -> ShowS
MatchInfo -> String
(Int -> MatchInfo -> ShowS)
-> (MatchInfo -> String)
-> ([MatchInfo] -> ShowS)
-> Show MatchInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MatchInfo -> ShowS
showsPrec :: Int -> MatchInfo -> ShowS
$cshow :: MatchInfo -> String
show :: MatchInfo -> String
$cshowList :: [MatchInfo] -> ShowS
showList :: [MatchInfo] -> ShowS
Show, ReadPrec [MatchInfo]
ReadPrec MatchInfo
Int -> ReadS MatchInfo
ReadS [MatchInfo]
(Int -> ReadS MatchInfo)
-> ReadS [MatchInfo]
-> ReadPrec MatchInfo
-> ReadPrec [MatchInfo]
-> Read MatchInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MatchInfo
readsPrec :: Int -> ReadS MatchInfo
$creadList :: ReadS [MatchInfo]
readList :: ReadS [MatchInfo]
$creadPrec :: ReadPrec MatchInfo
readPrec :: ReadPrec MatchInfo
$creadListPrec :: ReadPrec [MatchInfo]
readListPrec :: ReadPrec [MatchInfo]
Read)
data PartialDate
= Year { PartialDate -> Integer
year :: Integer }
| Month { year :: Integer, PartialDate -> Integer
month :: Integer }
| Day { year :: Integer, month :: Integer, PartialDate -> Integer
day :: Integer }
deriving (PartialDate -> PartialDate -> Bool
(PartialDate -> PartialDate -> Bool)
-> (PartialDate -> PartialDate -> Bool) -> Eq PartialDate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PartialDate -> PartialDate -> Bool
== :: PartialDate -> PartialDate -> Bool
$c/= :: PartialDate -> PartialDate -> Bool
/= :: PartialDate -> PartialDate -> Bool
Eq, Eq PartialDate
Eq PartialDate =>
(PartialDate -> PartialDate -> Ordering)
-> (PartialDate -> PartialDate -> Bool)
-> (PartialDate -> PartialDate -> Bool)
-> (PartialDate -> PartialDate -> Bool)
-> (PartialDate -> PartialDate -> Bool)
-> (PartialDate -> PartialDate -> PartialDate)
-> (PartialDate -> PartialDate -> PartialDate)
-> Ord PartialDate
PartialDate -> PartialDate -> Bool
PartialDate -> PartialDate -> Ordering
PartialDate -> PartialDate -> PartialDate
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PartialDate -> PartialDate -> Ordering
compare :: PartialDate -> PartialDate -> Ordering
$c< :: PartialDate -> PartialDate -> Bool
< :: PartialDate -> PartialDate -> Bool
$c<= :: PartialDate -> PartialDate -> Bool
<= :: PartialDate -> PartialDate -> Bool
$c> :: PartialDate -> PartialDate -> Bool
> :: PartialDate -> PartialDate -> Bool
$c>= :: PartialDate -> PartialDate -> Bool
>= :: PartialDate -> PartialDate -> Bool
$cmax :: PartialDate -> PartialDate -> PartialDate
max :: PartialDate -> PartialDate -> PartialDate
$cmin :: PartialDate -> PartialDate -> PartialDate
min :: PartialDate -> PartialDate -> PartialDate
Ord, Int -> PartialDate -> ShowS
[PartialDate] -> ShowS
PartialDate -> String
(Int -> PartialDate -> ShowS)
-> (PartialDate -> String)
-> ([PartialDate] -> ShowS)
-> Show PartialDate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PartialDate -> ShowS
showsPrec :: Int -> PartialDate -> ShowS
$cshow :: PartialDate -> String
show :: PartialDate -> String
$cshowList :: [PartialDate] -> ShowS
showList :: [PartialDate] -> ShowS
Show, ReadPrec [PartialDate]
ReadPrec PartialDate
Int -> ReadS PartialDate
ReadS [PartialDate]
(Int -> ReadS PartialDate)
-> ReadS [PartialDate]
-> ReadPrec PartialDate
-> ReadPrec [PartialDate]
-> Read PartialDate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PartialDate
readsPrec :: Int -> ReadS PartialDate
$creadList :: ReadS [PartialDate]
readList :: ReadS [PartialDate]
$creadPrec :: ReadPrec PartialDate
readPrec :: ReadPrec PartialDate
$creadListPrec :: ReadPrec [PartialDate]
readListPrec :: ReadPrec [PartialDate]
Read)
data FigureFlag
= Coordinates
| Name
| HiddenMoves
| RemoveCaptures
| Hoshi
deriving (FigureFlag -> FigureFlag -> Bool
(FigureFlag -> FigureFlag -> Bool)
-> (FigureFlag -> FigureFlag -> Bool) -> Eq FigureFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FigureFlag -> FigureFlag -> Bool
== :: FigureFlag -> FigureFlag -> Bool
$c/= :: FigureFlag -> FigureFlag -> Bool
/= :: FigureFlag -> FigureFlag -> Bool
Eq, Eq FigureFlag
Eq FigureFlag =>
(FigureFlag -> FigureFlag -> Ordering)
-> (FigureFlag -> FigureFlag -> Bool)
-> (FigureFlag -> FigureFlag -> Bool)
-> (FigureFlag -> FigureFlag -> Bool)
-> (FigureFlag -> FigureFlag -> Bool)
-> (FigureFlag -> FigureFlag -> FigureFlag)
-> (FigureFlag -> FigureFlag -> FigureFlag)
-> Ord FigureFlag
FigureFlag -> FigureFlag -> Bool
FigureFlag -> FigureFlag -> Ordering
FigureFlag -> FigureFlag -> FigureFlag
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FigureFlag -> FigureFlag -> Ordering
compare :: FigureFlag -> FigureFlag -> Ordering
$c< :: FigureFlag -> FigureFlag -> Bool
< :: FigureFlag -> FigureFlag -> Bool
$c<= :: FigureFlag -> FigureFlag -> Bool
<= :: FigureFlag -> FigureFlag -> Bool
$c> :: FigureFlag -> FigureFlag -> Bool
> :: FigureFlag -> FigureFlag -> Bool
$c>= :: FigureFlag -> FigureFlag -> Bool
>= :: FigureFlag -> FigureFlag -> Bool
$cmax :: FigureFlag -> FigureFlag -> FigureFlag
max :: FigureFlag -> FigureFlag -> FigureFlag
$cmin :: FigureFlag -> FigureFlag -> FigureFlag
min :: FigureFlag -> FigureFlag -> FigureFlag
Ord, Int -> FigureFlag -> ShowS
[FigureFlag] -> ShowS
FigureFlag -> String
(Int -> FigureFlag -> ShowS)
-> (FigureFlag -> String)
-> ([FigureFlag] -> ShowS)
-> Show FigureFlag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FigureFlag -> ShowS
showsPrec :: Int -> FigureFlag -> ShowS
$cshow :: FigureFlag -> String
show :: FigureFlag -> String
$cshowList :: [FigureFlag] -> ShowS
showList :: [FigureFlag] -> ShowS
Show, ReadPrec [FigureFlag]
ReadPrec FigureFlag
Int -> ReadS FigureFlag
ReadS [FigureFlag]
(Int -> ReadS FigureFlag)
-> ReadS [FigureFlag]
-> ReadPrec FigureFlag
-> ReadPrec [FigureFlag]
-> Read FigureFlag
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FigureFlag
readsPrec :: Int -> ReadS FigureFlag
$creadList :: ReadS [FigureFlag]
readList :: ReadS [FigureFlag]
$creadPrec :: ReadPrec FigureFlag
readPrec :: ReadPrec FigureFlag
$creadListPrec :: ReadPrec [FigureFlag]
readListPrec :: ReadPrec [FigureFlag]
Read, FigureFlag
FigureFlag -> FigureFlag -> Bounded FigureFlag
forall a. a -> a -> Bounded a
$cminBound :: FigureFlag
minBound :: FigureFlag
$cmaxBound :: FigureFlag
maxBound :: FigureFlag
Bounded)
allFigureFlags :: [FigureFlag]
allFigureFlags :: [FigureFlag]
allFigureFlags = [FigureFlag
Coordinates, FigureFlag
Name, FigureFlag
HiddenMoves, FigureFlag
RemoveCaptures, FigureFlag
Hoshi]
instance Enum FigureFlag where
toEnum :: Int -> FigureFlag
toEnum Int
0 = FigureFlag
Coordinates
toEnum Int
1 = FigureFlag
Name
toEnum Int
2 = FigureFlag
HiddenMoves
toEnum Int
8 = FigureFlag
RemoveCaptures
toEnum Int
9 = FigureFlag
Hoshi
toEnum Int
n = String -> FigureFlag
forall a. HasCallStack => String -> a
error (String -> FigureFlag) -> String -> FigureFlag
forall a b. (a -> b) -> a -> b
$ String
"unknown FigureFlag bit " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
fromEnum :: FigureFlag -> Int
fromEnum FigureFlag
Coordinates = Int
0
fromEnum FigureFlag
Name = Int
1
fromEnum FigureFlag
HiddenMoves = Int
2
fromEnum FigureFlag
RemoveCaptures = Int
8
fromEnum FigureFlag
Hoshi = Int
9
enumFrom :: FigureFlag -> [FigureFlag]
enumFrom FigureFlag
lo = (FigureFlag -> Bool) -> [FigureFlag] -> [FigureFlag]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (FigureFlag -> FigureFlag -> Bool
forall a. Eq a => a -> a -> Bool
/= FigureFlag
lo) [FigureFlag]
allFigureFlags
enumFromTo :: FigureFlag -> FigureFlag -> [FigureFlag]
enumFromTo FigureFlag
lo FigureFlag
hi = (FigureFlag -> Bool) -> [FigureFlag] -> [FigureFlag]
forall a. (a -> Bool) -> [a] -> [a]
filter (\FigureFlag
x -> FigureFlag
lo FigureFlag -> FigureFlag -> Bool
forall a. Ord a => a -> a -> Bool
<= FigureFlag
x Bool -> Bool -> Bool
&& FigureFlag
x FigureFlag -> FigureFlag -> Bool
forall a. Ord a => a -> a -> Bool
<= FigureFlag
hi) [FigureFlag]
allFigureFlags
succ :: FigureFlag -> FigureFlag
succ FigureFlag
lo = FigureFlag -> [FigureFlag]
forall a. Enum a => a -> [a]
enumFrom FigureFlag
lo [FigureFlag] -> Int -> FigureFlag
forall a. HasCallStack => [a] -> Int -> a
!! Int
1
pred :: FigureFlag -> FigureFlag
pred FigureFlag
hi = [FigureFlag] -> [FigureFlag]
forall a. [a] -> [a]
reverse (FigureFlag -> FigureFlag -> [FigureFlag]
forall a. Enum a => a -> a -> [a]
enumFromTo FigureFlag
forall a. Bounded a => a
minBound FigureFlag
hi) [FigureFlag] -> Int -> FigureFlag
forall a. HasCallStack => [a] -> Int -> a
!! Int
1
data Figure
= DefaultFigure
| NamedDefaultFigure String
| NamedFigure String (FigureFlag -> Bool)
deriving (Figure -> Figure -> Bool
(Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool) -> Eq Figure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Figure -> Figure -> Bool
== :: Figure -> Figure -> Bool
$c/= :: Figure -> Figure -> Bool
/= :: Figure -> Figure -> Bool
Eq, Eq Figure
Eq Figure =>
(Figure -> Figure -> Ordering)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Figure)
-> (Figure -> Figure -> Figure)
-> Ord Figure
Figure -> Figure -> Bool
Figure -> Figure -> Ordering
Figure -> Figure -> Figure
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Figure -> Figure -> Ordering
compare :: Figure -> Figure -> Ordering
$c< :: Figure -> Figure -> Bool
< :: Figure -> Figure -> Bool
$c<= :: Figure -> Figure -> Bool
<= :: Figure -> Figure -> Bool
$c> :: Figure -> Figure -> Bool
> :: Figure -> Figure -> Bool
$c>= :: Figure -> Figure -> Bool
>= :: Figure -> Figure -> Bool
$cmax :: Figure -> Figure -> Figure
max :: Figure -> Figure -> Figure
$cmin :: Figure -> Figure -> Figure
min :: Figure -> Figure -> Figure
Ord, Int -> Figure -> ShowS
[Figure] -> ShowS
Figure -> String
(Int -> Figure -> ShowS)
-> (Figure -> String) -> ([Figure] -> ShowS) -> Show Figure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Figure -> ShowS
showsPrec :: Int -> Figure -> ShowS
$cshow :: Figure -> String
show :: Figure -> String
$cshowList :: [Figure] -> ShowS
showList :: [Figure] -> ShowS
Show, ReadPrec [Figure]
ReadPrec Figure
Int -> ReadS Figure
ReadS [Figure]
(Int -> ReadS Figure)
-> ReadS [Figure]
-> ReadPrec Figure
-> ReadPrec [Figure]
-> Read Figure
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Figure
readsPrec :: Int -> ReadS Figure
$creadList :: ReadS [Figure]
readList :: ReadS [Figure]
$creadPrec :: ReadPrec Figure
readPrec :: ReadPrec Figure
$creadListPrec :: ReadPrec [Figure]
readListPrec :: ReadPrec [Figure]
Read)
mapFromFunction :: (t -> a) -> Map t a
mapFromFunction t -> a
f = [(t, a)] -> Map t a
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(t
k, t -> a
f t
k) | t
k <- [t
forall a. Bounded a => a
minBound..t
forall a. Bounded a => a
maxBound]]
instance (Bounded k, Enum k, Ord k, Show k, Show v) => Show (k -> v) where
showsPrec :: Int -> (k -> v) -> ShowS
showsPrec Int
n = Int -> Map k v -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
n (Map k v -> ShowS) -> ((k -> v) -> Map k v) -> (k -> v) -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> v) -> Map k v
forall {t} {a}. (Ord t, Bounded t, Enum t) => (t -> a) -> Map t a
mapFromFunction
instance (Bounded k, Enum k, Ord k, Read k, Read v) => Read (k -> v) where
readsPrec :: Int -> ReadS (k -> v)
readsPrec Int
n String
s = [((Map k v
m Map k v -> k -> v
forall k a. Ord k => Map k a -> k -> a
Map.!), String
rest) | (Map k v
m, String
rest) <- Int -> ReadS (Map k v)
forall a. Read a => Int -> ReadS a
readsPrec Int
n String
s, (k -> Bool) -> [k] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (k -> Map k v -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map k v
m) [k
forall a. Bounded a => a
minBound..]]
instance (Bounded k, Enum k, Ord k, Eq v) => Eq (k -> v) where
k -> v
f == :: (k -> v) -> (k -> v) -> Bool
== k -> v
g = (k -> v) -> Map k v
forall {t} {a}. (Ord t, Bounded t, Enum t) => (t -> a) -> Map t a
mapFromFunction k -> v
f Map k v -> Map k v -> Bool
forall a. Eq a => a -> a -> Bool
== (k -> v) -> Map k v
forall {t} {a}. (Ord t, Bounded t, Enum t) => (t -> a) -> Map t a
mapFromFunction k -> v
g
instance (Bounded k, Enum k, Ord k, Ord v) => Ord (k -> v) where
compare :: (k -> v) -> (k -> v) -> Ordering
compare = ((k -> v) -> Map k v) -> (k -> v) -> (k -> v) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (k -> v) -> Map k v
forall {t} {a}. (Ord t, Bounded t, Enum t) => (t -> a) -> Map t a
mapFromFunction
data Move move = Move {
forall move. Move move -> Maybe (Color, move)
move :: Maybe (Color, move),
forall move. Move move -> FuzzyBool
illegal :: FuzzyBool,
forall move. Move move -> Maybe Integer
number :: Maybe Integer,
forall move. Move move -> Maybe Quality
quality :: Maybe Quality,
forall move. Move move -> Maybe Rational
timeBlack :: Maybe Rational,
forall move. Move move -> Maybe Rational
timeWhite :: Maybe Rational,
forall move. Move move -> Maybe Integer
overtimeMovesBlack :: Maybe Integer,
forall move. Move move -> Maybe Integer
overtimeMovesWhite :: Maybe Integer
} deriving (Move move -> Move move -> Bool
(Move move -> Move move -> Bool)
-> (Move move -> Move move -> Bool) -> Eq (Move move)
forall move. Eq move => Move move -> Move move -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall move. Eq move => Move move -> Move move -> Bool
== :: Move move -> Move move -> Bool
$c/= :: forall move. Eq move => Move move -> Move move -> Bool
/= :: Move move -> Move move -> Bool
Eq, Eq (Move move)
Eq (Move move) =>
(Move move -> Move move -> Ordering)
-> (Move move -> Move move -> Bool)
-> (Move move -> Move move -> Bool)
-> (Move move -> Move move -> Bool)
-> (Move move -> Move move -> Bool)
-> (Move move -> Move move -> Move move)
-> (Move move -> Move move -> Move move)
-> Ord (Move move)
Move move -> Move move -> Bool
Move move -> Move move -> Ordering
Move move -> Move move -> Move move
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall move. Ord move => Eq (Move move)
forall move. Ord move => Move move -> Move move -> Bool
forall move. Ord move => Move move -> Move move -> Ordering
forall move. Ord move => Move move -> Move move -> Move move
$ccompare :: forall move. Ord move => Move move -> Move move -> Ordering
compare :: Move move -> Move move -> Ordering
$c< :: forall move. Ord move => Move move -> Move move -> Bool
< :: Move move -> Move move -> Bool
$c<= :: forall move. Ord move => Move move -> Move move -> Bool
<= :: Move move -> Move move -> Bool
$c> :: forall move. Ord move => Move move -> Move move -> Bool
> :: Move move -> Move move -> Bool
$c>= :: forall move. Ord move => Move move -> Move move -> Bool
>= :: Move move -> Move move -> Bool
$cmax :: forall move. Ord move => Move move -> Move move -> Move move
max :: Move move -> Move move -> Move move
$cmin :: forall move. Ord move => Move move -> Move move -> Move move
min :: Move move -> Move move -> Move move
Ord, Int -> Move move -> ShowS
[Move move] -> ShowS
Move move -> String
(Int -> Move move -> ShowS)
-> (Move move -> String)
-> ([Move move] -> ShowS)
-> Show (Move move)
forall move. Show move => Int -> Move move -> ShowS
forall move. Show move => [Move move] -> ShowS
forall move. Show move => Move move -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall move. Show move => Int -> Move move -> ShowS
showsPrec :: Int -> Move move -> ShowS
$cshow :: forall move. Show move => Move move -> String
show :: Move move -> String
$cshowList :: forall move. Show move => [Move move] -> ShowS
showList :: [Move move] -> ShowS
Show, ReadPrec [Move move]
ReadPrec (Move move)
Int -> ReadS (Move move)
ReadS [Move move]
(Int -> ReadS (Move move))
-> ReadS [Move move]
-> ReadPrec (Move move)
-> ReadPrec [Move move]
-> Read (Move move)
forall move. Read move => ReadPrec [Move move]
forall move. Read move => ReadPrec (Move move)
forall move. Read move => Int -> ReadS (Move move)
forall move. Read move => ReadS [Move move]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall move. Read move => Int -> ReadS (Move move)
readsPrec :: Int -> ReadS (Move move)
$creadList :: forall move. Read move => ReadS [Move move]
readList :: ReadS [Move move]
$creadPrec :: forall move. Read move => ReadPrec (Move move)
readPrec :: ReadPrec (Move move)
$creadListPrec :: forall move. Read move => ReadPrec [Move move]
readListPrec :: ReadPrec [Move move]
Read)
emptyMove :: Move move
emptyMove :: forall move. Move move
emptyMove = Maybe (Color, move)
-> FuzzyBool
-> Maybe Integer
-> Maybe Quality
-> Maybe Rational
-> Maybe Rational
-> Maybe Integer
-> Maybe Integer
-> Move move
forall move.
Maybe (Color, move)
-> FuzzyBool
-> Maybe Integer
-> Maybe Quality
-> Maybe Rational
-> Maybe Rational
-> Maybe Integer
-> Maybe Integer
-> Move move
Move Maybe (Color, move)
forall a. Maybe a
Nothing FuzzyBool
Possibly Maybe Integer
forall a. Maybe a
Nothing Maybe Quality
forall a. Maybe a
Nothing Maybe Rational
forall a. Maybe a
Nothing Maybe Rational
forall a. Maybe a
Nothing Maybe Integer
forall a. Maybe a
Nothing Maybe Integer
forall a. Maybe a
Nothing
data MoveGo = Pass | Play Point deriving (MoveGo -> MoveGo -> Bool
(MoveGo -> MoveGo -> Bool)
-> (MoveGo -> MoveGo -> Bool) -> Eq MoveGo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MoveGo -> MoveGo -> Bool
== :: MoveGo -> MoveGo -> Bool
$c/= :: MoveGo -> MoveGo -> Bool
/= :: MoveGo -> MoveGo -> Bool
Eq, Eq MoveGo
Eq MoveGo =>
(MoveGo -> MoveGo -> Ordering)
-> (MoveGo -> MoveGo -> Bool)
-> (MoveGo -> MoveGo -> Bool)
-> (MoveGo -> MoveGo -> Bool)
-> (MoveGo -> MoveGo -> Bool)
-> (MoveGo -> MoveGo -> MoveGo)
-> (MoveGo -> MoveGo -> MoveGo)
-> Ord MoveGo
MoveGo -> MoveGo -> Bool
MoveGo -> MoveGo -> Ordering
MoveGo -> MoveGo -> MoveGo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MoveGo -> MoveGo -> Ordering
compare :: MoveGo -> MoveGo -> Ordering
$c< :: MoveGo -> MoveGo -> Bool
< :: MoveGo -> MoveGo -> Bool
$c<= :: MoveGo -> MoveGo -> Bool
<= :: MoveGo -> MoveGo -> Bool
$c> :: MoveGo -> MoveGo -> Bool
> :: MoveGo -> MoveGo -> Bool
$c>= :: MoveGo -> MoveGo -> Bool
>= :: MoveGo -> MoveGo -> Bool
$cmax :: MoveGo -> MoveGo -> MoveGo
max :: MoveGo -> MoveGo -> MoveGo
$cmin :: MoveGo -> MoveGo -> MoveGo
min :: MoveGo -> MoveGo -> MoveGo
Ord, Int -> MoveGo -> ShowS
[MoveGo] -> ShowS
MoveGo -> String
(Int -> MoveGo -> ShowS)
-> (MoveGo -> String) -> ([MoveGo] -> ShowS) -> Show MoveGo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MoveGo -> ShowS
showsPrec :: Int -> MoveGo -> ShowS
$cshow :: MoveGo -> String
show :: MoveGo -> String
$cshowList :: [MoveGo] -> ShowS
showList :: [MoveGo] -> ShowS
Show, ReadPrec [MoveGo]
ReadPrec MoveGo
Int -> ReadS MoveGo
ReadS [MoveGo]
(Int -> ReadS MoveGo)
-> ReadS [MoveGo]
-> ReadPrec MoveGo
-> ReadPrec [MoveGo]
-> Read MoveGo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MoveGo
readsPrec :: Int -> ReadS MoveGo
$creadList :: ReadS [MoveGo]
readList :: ReadS [MoveGo]
$creadPrec :: ReadPrec MoveGo
readPrec :: ReadPrec MoveGo
$creadListPrec :: ReadPrec [MoveGo]
readListPrec :: ReadPrec [MoveGo]
Read)
data Setup stone = Setup {
forall stone. Setup stone -> Set stone
addBlack :: Set stone,
forall stone. Setup stone -> Set stone
addWhite :: Set stone,
forall stone. Setup stone -> Set Point
remove :: Set Point,
forall stone. Setup stone -> Maybe Color
toPlay :: Maybe Color
} deriving (Setup stone -> Setup stone -> Bool
(Setup stone -> Setup stone -> Bool)
-> (Setup stone -> Setup stone -> Bool) -> Eq (Setup stone)
forall stone. Eq stone => Setup stone -> Setup stone -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall stone. Eq stone => Setup stone -> Setup stone -> Bool
== :: Setup stone -> Setup stone -> Bool
$c/= :: forall stone. Eq stone => Setup stone -> Setup stone -> Bool
/= :: Setup stone -> Setup stone -> Bool
Eq, Eq (Setup stone)
Eq (Setup stone) =>
(Setup stone -> Setup stone -> Ordering)
-> (Setup stone -> Setup stone -> Bool)
-> (Setup stone -> Setup stone -> Bool)
-> (Setup stone -> Setup stone -> Bool)
-> (Setup stone -> Setup stone -> Bool)
-> (Setup stone -> Setup stone -> Setup stone)
-> (Setup stone -> Setup stone -> Setup stone)
-> Ord (Setup stone)
Setup stone -> Setup stone -> Bool
Setup stone -> Setup stone -> Ordering
Setup stone -> Setup stone -> Setup stone
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall stone. Ord stone => Eq (Setup stone)
forall stone. Ord stone => Setup stone -> Setup stone -> Bool
forall stone. Ord stone => Setup stone -> Setup stone -> Ordering
forall stone.
Ord stone =>
Setup stone -> Setup stone -> Setup stone
$ccompare :: forall stone. Ord stone => Setup stone -> Setup stone -> Ordering
compare :: Setup stone -> Setup stone -> Ordering
$c< :: forall stone. Ord stone => Setup stone -> Setup stone -> Bool
< :: Setup stone -> Setup stone -> Bool
$c<= :: forall stone. Ord stone => Setup stone -> Setup stone -> Bool
<= :: Setup stone -> Setup stone -> Bool
$c> :: forall stone. Ord stone => Setup stone -> Setup stone -> Bool
> :: Setup stone -> Setup stone -> Bool
$c>= :: forall stone. Ord stone => Setup stone -> Setup stone -> Bool
>= :: Setup stone -> Setup stone -> Bool
$cmax :: forall stone.
Ord stone =>
Setup stone -> Setup stone -> Setup stone
max :: Setup stone -> Setup stone -> Setup stone
$cmin :: forall stone.
Ord stone =>
Setup stone -> Setup stone -> Setup stone
min :: Setup stone -> Setup stone -> Setup stone
Ord, Int -> Setup stone -> ShowS
[Setup stone] -> ShowS
Setup stone -> String
(Int -> Setup stone -> ShowS)
-> (Setup stone -> String)
-> ([Setup stone] -> ShowS)
-> Show (Setup stone)
forall stone. Show stone => Int -> Setup stone -> ShowS
forall stone. Show stone => [Setup stone] -> ShowS
forall stone. Show stone => Setup stone -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall stone. Show stone => Int -> Setup stone -> ShowS
showsPrec :: Int -> Setup stone -> ShowS
$cshow :: forall stone. Show stone => Setup stone -> String
show :: Setup stone -> String
$cshowList :: forall stone. Show stone => [Setup stone] -> ShowS
showList :: [Setup stone] -> ShowS
Show, ReadPrec [Setup stone]
ReadPrec (Setup stone)
Int -> ReadS (Setup stone)
ReadS [Setup stone]
(Int -> ReadS (Setup stone))
-> ReadS [Setup stone]
-> ReadPrec (Setup stone)
-> ReadPrec [Setup stone]
-> Read (Setup stone)
forall stone. (Read stone, Ord stone) => ReadPrec [Setup stone]
forall stone. (Read stone, Ord stone) => ReadPrec (Setup stone)
forall stone. (Read stone, Ord stone) => Int -> ReadS (Setup stone)
forall stone. (Read stone, Ord stone) => ReadS [Setup stone]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall stone. (Read stone, Ord stone) => Int -> ReadS (Setup stone)
readsPrec :: Int -> ReadS (Setup stone)
$creadList :: forall stone. (Read stone, Ord stone) => ReadS [Setup stone]
readList :: ReadS [Setup stone]
$creadPrec :: forall stone. (Read stone, Ord stone) => ReadPrec (Setup stone)
readPrec :: ReadPrec (Setup stone)
$creadListPrec :: forall stone. (Read stone, Ord stone) => ReadPrec [Setup stone]
readListPrec :: ReadPrec [Setup stone]
Read)
emptySetup :: Setup stone
emptySetup :: forall stone. Setup stone
emptySetup = Set stone -> Set stone -> Set Point -> Maybe Color -> Setup stone
forall stone.
Set stone -> Set stone -> Set Point -> Maybe Color -> Setup stone
Setup Set stone
forall a. Set a
Set.empty Set stone
forall a. Set a
Set.empty Set Point
forall a. Set a
Set.empty Maybe Color
forall a. Maybe a
Nothing
data GameInfo ruleSet extra = GameInfo {
forall ruleSet extra. GameInfo ruleSet extra -> Maybe Rank
rankBlack :: Maybe Rank,
forall ruleSet extra. GameInfo ruleSet extra -> Maybe Rank
rankWhite :: Maybe Rank,
forall ruleSet extra. GameInfo ruleSet extra -> Set PartialDate
date :: Set PartialDate,
forall ruleSet extra. GameInfo ruleSet extra -> Maybe Round
round :: Maybe Round,
forall ruleSet extra.
GameInfo ruleSet extra -> Maybe (RuleSet ruleSet)
ruleSet :: Maybe (RuleSet ruleSet),
forall ruleSet extra. GameInfo ruleSet extra -> Maybe Rational
timeLimit :: Maybe Rational,
forall ruleSet extra. GameInfo ruleSet extra -> Maybe GameResult
result :: Maybe GameResult,
forall ruleSet extra.
GameInfo ruleSet extra -> Map GameInfoType String
freeform :: Map GameInfoType String,
forall ruleSet extra. GameInfo ruleSet extra -> extra
otherGameInfo :: extra
} deriving (GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
(GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool)
-> (GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool)
-> Eq (GameInfo ruleSet extra)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall ruleSet extra.
(Eq ruleSet, Eq extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
$c== :: forall ruleSet extra.
(Eq ruleSet, Eq extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
== :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
$c/= :: forall ruleSet extra.
(Eq ruleSet, Eq extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
/= :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
Eq, Eq (GameInfo ruleSet extra)
Eq (GameInfo ruleSet extra) =>
(GameInfo ruleSet extra -> GameInfo ruleSet extra -> Ordering)
-> (GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool)
-> (GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool)
-> (GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool)
-> (GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool)
-> (GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra)
-> (GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra)
-> Ord (GameInfo ruleSet extra)
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Ordering
GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
Eq (GameInfo ruleSet extra)
forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Ordering
forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra
$ccompare :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Ordering
compare :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Ordering
$c< :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
< :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
$c<= :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
<= :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
$c> :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
> :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
$c>= :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
>= :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool
$cmax :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra
max :: GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra
$cmin :: forall ruleSet extra.
(Ord ruleSet, Ord extra) =>
GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra
min :: GameInfo ruleSet extra
-> GameInfo ruleSet extra -> GameInfo ruleSet extra
Ord, Int -> GameInfo ruleSet extra -> ShowS
[GameInfo ruleSet extra] -> ShowS
GameInfo ruleSet extra -> String
(Int -> GameInfo ruleSet extra -> ShowS)
-> (GameInfo ruleSet extra -> String)
-> ([GameInfo ruleSet extra] -> ShowS)
-> Show (GameInfo ruleSet extra)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall ruleSet extra.
(Show ruleSet, Show extra) =>
Int -> GameInfo ruleSet extra -> ShowS
forall ruleSet extra.
(Show ruleSet, Show extra) =>
[GameInfo ruleSet extra] -> ShowS
forall ruleSet extra.
(Show ruleSet, Show extra) =>
GameInfo ruleSet extra -> String
$cshowsPrec :: forall ruleSet extra.
(Show ruleSet, Show extra) =>
Int -> GameInfo ruleSet extra -> ShowS
showsPrec :: Int -> GameInfo ruleSet extra -> ShowS
$cshow :: forall ruleSet extra.
(Show ruleSet, Show extra) =>
GameInfo ruleSet extra -> String
show :: GameInfo ruleSet extra -> String
$cshowList :: forall ruleSet extra.
(Show ruleSet, Show extra) =>
[GameInfo ruleSet extra] -> ShowS
showList :: [GameInfo ruleSet extra] -> ShowS
Show, ReadPrec [GameInfo ruleSet extra]
ReadPrec (GameInfo ruleSet extra)
Int -> ReadS (GameInfo ruleSet extra)
ReadS [GameInfo ruleSet extra]
(Int -> ReadS (GameInfo ruleSet extra))
-> ReadS [GameInfo ruleSet extra]
-> ReadPrec (GameInfo ruleSet extra)
-> ReadPrec [GameInfo ruleSet extra]
-> Read (GameInfo ruleSet extra)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall ruleSet extra.
(Read ruleSet, Read extra) =>
ReadPrec [GameInfo ruleSet extra]
forall ruleSet extra.
(Read ruleSet, Read extra) =>
ReadPrec (GameInfo ruleSet extra)
forall ruleSet extra.
(Read ruleSet, Read extra) =>
Int -> ReadS (GameInfo ruleSet extra)
forall ruleSet extra.
(Read ruleSet, Read extra) =>
ReadS [GameInfo ruleSet extra]
$creadsPrec :: forall ruleSet extra.
(Read ruleSet, Read extra) =>
Int -> ReadS (GameInfo ruleSet extra)
readsPrec :: Int -> ReadS (GameInfo ruleSet extra)
$creadList :: forall ruleSet extra.
(Read ruleSet, Read extra) =>
ReadS [GameInfo ruleSet extra]
readList :: ReadS [GameInfo ruleSet extra]
$creadPrec :: forall ruleSet extra.
(Read ruleSet, Read extra) =>
ReadPrec (GameInfo ruleSet extra)
readPrec :: ReadPrec (GameInfo ruleSet extra)
$creadListPrec :: forall ruleSet extra.
(Read ruleSet, Read extra) =>
ReadPrec [GameInfo ruleSet extra]
readListPrec :: ReadPrec [GameInfo ruleSet extra]
Read)
emptyGameInfo :: GameInfo ruleSet ()
emptyGameInfo :: forall ruleSet. GameInfo ruleSet ()
emptyGameInfo = Maybe Rank
-> Maybe Rank
-> Set PartialDate
-> Maybe Round
-> Maybe (RuleSet ruleSet)
-> Maybe Rational
-> Maybe GameResult
-> Map GameInfoType String
-> ()
-> GameInfo ruleSet ()
forall ruleSet extra.
Maybe Rank
-> Maybe Rank
-> Set PartialDate
-> Maybe Round
-> Maybe (RuleSet ruleSet)
-> Maybe Rational
-> Maybe GameResult
-> Map GameInfoType String
-> extra
-> GameInfo ruleSet extra
GameInfo Maybe Rank
forall a. Maybe a
Nothing Maybe Rank
forall a. Maybe a
Nothing Set PartialDate
forall a. Set a
Set.empty Maybe Round
forall a. Maybe a
Nothing Maybe (RuleSet ruleSet)
forall a. Maybe a
Nothing Maybe Rational
forall a. Maybe a
Nothing Maybe GameResult
forall a. Maybe a
Nothing Map GameInfoType String
forall k a. Map k a
Map.empty ()
data GameInfoGo = GameInfoGo {
GameInfoGo -> Maybe Integer
handicap :: Maybe Integer,
GameInfoGo -> Maybe Rational
komi :: Maybe Rational
} deriving (GameInfoGo -> GameInfoGo -> Bool
(GameInfoGo -> GameInfoGo -> Bool)
-> (GameInfoGo -> GameInfoGo -> Bool) -> Eq GameInfoGo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameInfoGo -> GameInfoGo -> Bool
== :: GameInfoGo -> GameInfoGo -> Bool
$c/= :: GameInfoGo -> GameInfoGo -> Bool
/= :: GameInfoGo -> GameInfoGo -> Bool
Eq, Eq GameInfoGo
Eq GameInfoGo =>
(GameInfoGo -> GameInfoGo -> Ordering)
-> (GameInfoGo -> GameInfoGo -> Bool)
-> (GameInfoGo -> GameInfoGo -> Bool)
-> (GameInfoGo -> GameInfoGo -> Bool)
-> (GameInfoGo -> GameInfoGo -> Bool)
-> (GameInfoGo -> GameInfoGo -> GameInfoGo)
-> (GameInfoGo -> GameInfoGo -> GameInfoGo)
-> Ord GameInfoGo
GameInfoGo -> GameInfoGo -> Bool
GameInfoGo -> GameInfoGo -> Ordering
GameInfoGo -> GameInfoGo -> GameInfoGo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameInfoGo -> GameInfoGo -> Ordering
compare :: GameInfoGo -> GameInfoGo -> Ordering
$c< :: GameInfoGo -> GameInfoGo -> Bool
< :: GameInfoGo -> GameInfoGo -> Bool
$c<= :: GameInfoGo -> GameInfoGo -> Bool
<= :: GameInfoGo -> GameInfoGo -> Bool
$c> :: GameInfoGo -> GameInfoGo -> Bool
> :: GameInfoGo -> GameInfoGo -> Bool
$c>= :: GameInfoGo -> GameInfoGo -> Bool
>= :: GameInfoGo -> GameInfoGo -> Bool
$cmax :: GameInfoGo -> GameInfoGo -> GameInfoGo
max :: GameInfoGo -> GameInfoGo -> GameInfoGo
$cmin :: GameInfoGo -> GameInfoGo -> GameInfoGo
min :: GameInfoGo -> GameInfoGo -> GameInfoGo
Ord, Int -> GameInfoGo -> ShowS
[GameInfoGo] -> ShowS
GameInfoGo -> String
(Int -> GameInfoGo -> ShowS)
-> (GameInfoGo -> String)
-> ([GameInfoGo] -> ShowS)
-> Show GameInfoGo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameInfoGo -> ShowS
showsPrec :: Int -> GameInfoGo -> ShowS
$cshow :: GameInfoGo -> String
show :: GameInfoGo -> String
$cshowList :: [GameInfoGo] -> ShowS
showList :: [GameInfoGo] -> ShowS
Show, ReadPrec [GameInfoGo]
ReadPrec GameInfoGo
Int -> ReadS GameInfoGo
ReadS [GameInfoGo]
(Int -> ReadS GameInfoGo)
-> ReadS [GameInfoGo]
-> ReadPrec GameInfoGo
-> ReadPrec [GameInfoGo]
-> Read GameInfoGo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameInfoGo
readsPrec :: Int -> ReadS GameInfoGo
$creadList :: ReadS [GameInfoGo]
readList :: ReadS [GameInfoGo]
$creadPrec :: ReadPrec GameInfoGo
readPrec :: ReadPrec GameInfoGo
$creadListPrec :: ReadPrec [GameInfoGo]
readListPrec :: ReadPrec [GameInfoGo]
Read)
type GameInfoBackgammon = [MatchInfo]
data GameInfoLinesOfAction = GameInfoLinesOfAction {
GameInfoLinesOfAction -> InitialPosition
initialPositionLOA :: InitialPosition,
GameInfoLinesOfAction -> Bool
invertYAxis :: Bool,
GameInfoLinesOfAction -> InitialPlacement
initialPlacement :: InitialPlacement
} deriving (GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
(GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool)
-> (GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool)
-> Eq GameInfoLinesOfAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
== :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
$c/= :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
/= :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
Eq, Eq GameInfoLinesOfAction
Eq GameInfoLinesOfAction =>
(GameInfoLinesOfAction -> GameInfoLinesOfAction -> Ordering)
-> (GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool)
-> (GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool)
-> (GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool)
-> (GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool)
-> (GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction)
-> (GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction)
-> Ord GameInfoLinesOfAction
GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
GameInfoLinesOfAction -> GameInfoLinesOfAction -> Ordering
GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Ordering
compare :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Ordering
$c< :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
< :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
$c<= :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
<= :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
$c> :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
> :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
$c>= :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
>= :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool
$cmax :: GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction
max :: GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction
$cmin :: GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction
min :: GameInfoLinesOfAction
-> GameInfoLinesOfAction -> GameInfoLinesOfAction
Ord, Int -> GameInfoLinesOfAction -> ShowS
[GameInfoLinesOfAction] -> ShowS
GameInfoLinesOfAction -> String
(Int -> GameInfoLinesOfAction -> ShowS)
-> (GameInfoLinesOfAction -> String)
-> ([GameInfoLinesOfAction] -> ShowS)
-> Show GameInfoLinesOfAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameInfoLinesOfAction -> ShowS
showsPrec :: Int -> GameInfoLinesOfAction -> ShowS
$cshow :: GameInfoLinesOfAction -> String
show :: GameInfoLinesOfAction -> String
$cshowList :: [GameInfoLinesOfAction] -> ShowS
showList :: [GameInfoLinesOfAction] -> ShowS
Show, ReadPrec [GameInfoLinesOfAction]
ReadPrec GameInfoLinesOfAction
Int -> ReadS GameInfoLinesOfAction
ReadS [GameInfoLinesOfAction]
(Int -> ReadS GameInfoLinesOfAction)
-> ReadS [GameInfoLinesOfAction]
-> ReadPrec GameInfoLinesOfAction
-> ReadPrec [GameInfoLinesOfAction]
-> Read GameInfoLinesOfAction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameInfoLinesOfAction
readsPrec :: Int -> ReadS GameInfoLinesOfAction
$creadList :: ReadS [GameInfoLinesOfAction]
readList :: ReadS [GameInfoLinesOfAction]
$creadPrec :: ReadPrec GameInfoLinesOfAction
readPrec :: ReadPrec GameInfoLinesOfAction
$creadListPrec :: ReadPrec [GameInfoLinesOfAction]
readListPrec :: ReadPrec [GameInfoLinesOfAction]
Read)
type GameInfoHex = Bool
data GameInfoOcti = GameInfoOcti {
GameInfoOcti -> Set Point
squaresWhite :: Set Point,
GameInfoOcti -> Set Point
squaresBlack :: Set Point,
GameInfoOcti -> Integer
prongs :: Integer,
GameInfoOcti -> Integer
reserve :: Integer,
GameInfoOcti -> Integer
superProngs :: Integer
} deriving (GameInfoOcti -> GameInfoOcti -> Bool
(GameInfoOcti -> GameInfoOcti -> Bool)
-> (GameInfoOcti -> GameInfoOcti -> Bool) -> Eq GameInfoOcti
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameInfoOcti -> GameInfoOcti -> Bool
== :: GameInfoOcti -> GameInfoOcti -> Bool
$c/= :: GameInfoOcti -> GameInfoOcti -> Bool
/= :: GameInfoOcti -> GameInfoOcti -> Bool
Eq, Eq GameInfoOcti
Eq GameInfoOcti =>
(GameInfoOcti -> GameInfoOcti -> Ordering)
-> (GameInfoOcti -> GameInfoOcti -> Bool)
-> (GameInfoOcti -> GameInfoOcti -> Bool)
-> (GameInfoOcti -> GameInfoOcti -> Bool)
-> (GameInfoOcti -> GameInfoOcti -> Bool)
-> (GameInfoOcti -> GameInfoOcti -> GameInfoOcti)
-> (GameInfoOcti -> GameInfoOcti -> GameInfoOcti)
-> Ord GameInfoOcti
GameInfoOcti -> GameInfoOcti -> Bool
GameInfoOcti -> GameInfoOcti -> Ordering
GameInfoOcti -> GameInfoOcti -> GameInfoOcti
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameInfoOcti -> GameInfoOcti -> Ordering
compare :: GameInfoOcti -> GameInfoOcti -> Ordering
$c< :: GameInfoOcti -> GameInfoOcti -> Bool
< :: GameInfoOcti -> GameInfoOcti -> Bool
$c<= :: GameInfoOcti -> GameInfoOcti -> Bool
<= :: GameInfoOcti -> GameInfoOcti -> Bool
$c> :: GameInfoOcti -> GameInfoOcti -> Bool
> :: GameInfoOcti -> GameInfoOcti -> Bool
$c>= :: GameInfoOcti -> GameInfoOcti -> Bool
>= :: GameInfoOcti -> GameInfoOcti -> Bool
$cmax :: GameInfoOcti -> GameInfoOcti -> GameInfoOcti
max :: GameInfoOcti -> GameInfoOcti -> GameInfoOcti
$cmin :: GameInfoOcti -> GameInfoOcti -> GameInfoOcti
min :: GameInfoOcti -> GameInfoOcti -> GameInfoOcti
Ord, Int -> GameInfoOcti -> ShowS
[GameInfoOcti] -> ShowS
GameInfoOcti -> String
(Int -> GameInfoOcti -> ShowS)
-> (GameInfoOcti -> String)
-> ([GameInfoOcti] -> ShowS)
-> Show GameInfoOcti
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameInfoOcti -> ShowS
showsPrec :: Int -> GameInfoOcti -> ShowS
$cshow :: GameInfoOcti -> String
show :: GameInfoOcti -> String
$cshowList :: [GameInfoOcti] -> ShowS
showList :: [GameInfoOcti] -> ShowS
Show, ReadPrec [GameInfoOcti]
ReadPrec GameInfoOcti
Int -> ReadS GameInfoOcti
ReadS [GameInfoOcti]
(Int -> ReadS GameInfoOcti)
-> ReadS [GameInfoOcti]
-> ReadPrec GameInfoOcti
-> ReadPrec [GameInfoOcti]
-> Read GameInfoOcti
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameInfoOcti
readsPrec :: Int -> ReadS GameInfoOcti
$creadList :: ReadS [GameInfoOcti]
readList :: ReadS [GameInfoOcti]
$creadPrec :: ReadPrec GameInfoOcti
readPrec :: ReadPrec GameInfoOcti
$creadListPrec :: ReadPrec [GameInfoOcti]
readListPrec :: ReadPrec [GameInfoOcti]
Read)
data Annotation extra = Annotation {
:: Maybe String,
forall extra. Annotation extra -> Maybe String
name :: Maybe String,
forall extra. Annotation extra -> Maybe Emphasis
hotspot :: Maybe Emphasis,
forall extra. Annotation extra -> Maybe Rational
value :: Maybe Rational,
forall extra. Annotation extra -> Maybe (Judgment, Emphasis)
judgment :: Maybe (Judgment, Emphasis),
forall extra. Annotation extra -> extra
otherAnnotation :: extra
} deriving (Annotation extra -> Annotation extra -> Bool
(Annotation extra -> Annotation extra -> Bool)
-> (Annotation extra -> Annotation extra -> Bool)
-> Eq (Annotation extra)
forall extra.
Eq extra =>
Annotation extra -> Annotation extra -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall extra.
Eq extra =>
Annotation extra -> Annotation extra -> Bool
== :: Annotation extra -> Annotation extra -> Bool
$c/= :: forall extra.
Eq extra =>
Annotation extra -> Annotation extra -> Bool
/= :: Annotation extra -> Annotation extra -> Bool
Eq, Eq (Annotation extra)
Eq (Annotation extra) =>
(Annotation extra -> Annotation extra -> Ordering)
-> (Annotation extra -> Annotation extra -> Bool)
-> (Annotation extra -> Annotation extra -> Bool)
-> (Annotation extra -> Annotation extra -> Bool)
-> (Annotation extra -> Annotation extra -> Bool)
-> (Annotation extra -> Annotation extra -> Annotation extra)
-> (Annotation extra -> Annotation extra -> Annotation extra)
-> Ord (Annotation extra)
Annotation extra -> Annotation extra -> Bool
Annotation extra -> Annotation extra -> Ordering
Annotation extra -> Annotation extra -> Annotation extra
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall extra. Ord extra => Eq (Annotation extra)
forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Bool
forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Ordering
forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Annotation extra
$ccompare :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Ordering
compare :: Annotation extra -> Annotation extra -> Ordering
$c< :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Bool
< :: Annotation extra -> Annotation extra -> Bool
$c<= :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Bool
<= :: Annotation extra -> Annotation extra -> Bool
$c> :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Bool
> :: Annotation extra -> Annotation extra -> Bool
$c>= :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Bool
>= :: Annotation extra -> Annotation extra -> Bool
$cmax :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Annotation extra
max :: Annotation extra -> Annotation extra -> Annotation extra
$cmin :: forall extra.
Ord extra =>
Annotation extra -> Annotation extra -> Annotation extra
min :: Annotation extra -> Annotation extra -> Annotation extra
Ord, Int -> Annotation extra -> ShowS
[Annotation extra] -> ShowS
Annotation extra -> String
(Int -> Annotation extra -> ShowS)
-> (Annotation extra -> String)
-> ([Annotation extra] -> ShowS)
-> Show (Annotation extra)
forall extra. Show extra => Int -> Annotation extra -> ShowS
forall extra. Show extra => [Annotation extra] -> ShowS
forall extra. Show extra => Annotation extra -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall extra. Show extra => Int -> Annotation extra -> ShowS
showsPrec :: Int -> Annotation extra -> ShowS
$cshow :: forall extra. Show extra => Annotation extra -> String
show :: Annotation extra -> String
$cshowList :: forall extra. Show extra => [Annotation extra] -> ShowS
showList :: [Annotation extra] -> ShowS
Show, ReadPrec [Annotation extra]
ReadPrec (Annotation extra)
Int -> ReadS (Annotation extra)
ReadS [Annotation extra]
(Int -> ReadS (Annotation extra))
-> ReadS [Annotation extra]
-> ReadPrec (Annotation extra)
-> ReadPrec [Annotation extra]
-> Read (Annotation extra)
forall extra. Read extra => ReadPrec [Annotation extra]
forall extra. Read extra => ReadPrec (Annotation extra)
forall extra. Read extra => Int -> ReadS (Annotation extra)
forall extra. Read extra => ReadS [Annotation extra]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall extra. Read extra => Int -> ReadS (Annotation extra)
readsPrec :: Int -> ReadS (Annotation extra)
$creadList :: forall extra. Read extra => ReadS [Annotation extra]
readList :: ReadS [Annotation extra]
$creadPrec :: forall extra. Read extra => ReadPrec (Annotation extra)
readPrec :: ReadPrec (Annotation extra)
$creadListPrec :: forall extra. Read extra => ReadPrec [Annotation extra]
readListPrec :: ReadPrec [Annotation extra]
Read)
emptyAnnotation :: Annotation ()
emptyAnnotation :: Annotation ()
emptyAnnotation = Maybe String
-> Maybe String
-> Maybe Emphasis
-> Maybe Rational
-> Maybe (Judgment, Emphasis)
-> ()
-> Annotation ()
forall extra.
Maybe String
-> Maybe String
-> Maybe Emphasis
-> Maybe Rational
-> Maybe (Judgment, Emphasis)
-> extra
-> Annotation extra
Annotation Maybe String
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing Maybe Emphasis
forall a. Maybe a
Nothing Maybe Rational
forall a. Maybe a
Nothing Maybe (Judgment, Emphasis)
forall a. Maybe a
Nothing ()
type AnnotationGo = Map Color (Set Point)
data Markup = Markup {
Markup -> Map Point Mark
marks :: Map Point Mark,
Markup -> Map Point String
labels :: Map Point String,
Markup -> Set (Point, Point)
arrows :: Set (Point, Point),
Markup -> Set (Point, Point)
lines :: Set (Point, Point),
Markup -> Maybe (Set Point)
dim :: Maybe (Set Point),
Markup -> Maybe (Set Point)
visible :: Maybe (Set Point),
Markup -> Maybe Numbering
numbering :: Maybe Numbering,
Markup -> Maybe Figure
figure :: Maybe Figure
} deriving (Markup -> Markup -> Bool
(Markup -> Markup -> Bool)
-> (Markup -> Markup -> Bool) -> Eq Markup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Markup -> Markup -> Bool
== :: Markup -> Markup -> Bool
$c/= :: Markup -> Markup -> Bool
/= :: Markup -> Markup -> Bool
Eq, Eq Markup
Eq Markup =>
(Markup -> Markup -> Ordering)
-> (Markup -> Markup -> Bool)
-> (Markup -> Markup -> Bool)
-> (Markup -> Markup -> Bool)
-> (Markup -> Markup -> Bool)
-> (Markup -> Markup -> Markup)
-> (Markup -> Markup -> Markup)
-> Ord Markup
Markup -> Markup -> Bool
Markup -> Markup -> Ordering
Markup -> Markup -> Markup
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Markup -> Markup -> Ordering
compare :: Markup -> Markup -> Ordering
$c< :: Markup -> Markup -> Bool
< :: Markup -> Markup -> Bool
$c<= :: Markup -> Markup -> Bool
<= :: Markup -> Markup -> Bool
$c> :: Markup -> Markup -> Bool
> :: Markup -> Markup -> Bool
$c>= :: Markup -> Markup -> Bool
>= :: Markup -> Markup -> Bool
$cmax :: Markup -> Markup -> Markup
max :: Markup -> Markup -> Markup
$cmin :: Markup -> Markup -> Markup
min :: Markup -> Markup -> Markup
Ord, Int -> Markup -> ShowS
[Markup] -> ShowS
Markup -> String
(Int -> Markup -> ShowS)
-> (Markup -> String) -> ([Markup] -> ShowS) -> Show Markup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Markup -> ShowS
showsPrec :: Int -> Markup -> ShowS
$cshow :: Markup -> String
show :: Markup -> String
$cshowList :: [Markup] -> ShowS
showList :: [Markup] -> ShowS
Show, ReadPrec [Markup]
ReadPrec Markup
Int -> ReadS Markup
ReadS [Markup]
(Int -> ReadS Markup)
-> ReadS [Markup]
-> ReadPrec Markup
-> ReadPrec [Markup]
-> Read Markup
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Markup
readsPrec :: Int -> ReadS Markup
$creadList :: ReadS [Markup]
readList :: ReadS [Markup]
$creadPrec :: ReadPrec Markup
readPrec :: ReadPrec Markup
$creadListPrec :: ReadPrec [Markup]
readListPrec :: ReadPrec [Markup]
Read)
emptyMarkup :: Markup
emptyMarkup :: Markup
emptyMarkup = Map Point Mark
-> Map Point String
-> Set (Point, Point)
-> Set (Point, Point)
-> Maybe (Set Point)
-> Maybe (Set Point)
-> Maybe Numbering
-> Maybe Figure
-> Markup
Markup Map Point Mark
forall k a. Map k a
Map.empty Map Point String
forall k a. Map k a
Map.empty Set (Point, Point)
forall a. Set a
Set.empty Set (Point, Point)
forall a. Set a
Set.empty Maybe (Set Point)
forall a. Maybe a
Nothing Maybe (Set Point)
forall a. Maybe a
Nothing Maybe Numbering
forall a. Maybe a
Nothing Maybe Figure
forall a. Maybe a
Nothing
data Game = Game {
Game -> Maybe (String, String)
application :: Maybe (Application, Version),
Game -> Maybe (VariationType, Bool)
variationType :: Maybe (VariationType, AutoMarkup),
Game -> Maybe Point
size :: Maybe (Integer, Integer),
Game -> GameTree
tree :: GameTree
} deriving (Game -> Game -> Bool
(Game -> Game -> Bool) -> (Game -> Game -> Bool) -> Eq Game
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Game -> Game -> Bool
== :: Game -> Game -> Bool
$c/= :: Game -> Game -> Bool
/= :: Game -> Game -> Bool
Eq, Int -> Game -> ShowS
[Game] -> ShowS
Game -> String
(Int -> Game -> ShowS)
-> (Game -> String) -> ([Game] -> ShowS) -> Show Game
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Game -> ShowS
showsPrec :: Int -> Game -> ShowS
$cshow :: Game -> String
show :: Game -> String
$cshowList :: [Game] -> ShowS
showList :: [Game] -> ShowS
Show, ReadPrec [Game]
ReadPrec Game
Int -> ReadS Game
ReadS [Game]
(Int -> ReadS Game)
-> ReadS [Game] -> ReadPrec Game -> ReadPrec [Game] -> Read Game
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Game
readsPrec :: Int -> ReadS Game
$creadList :: ReadS [Game]
readList :: ReadS [Game]
$creadPrec :: ReadPrec Game
readPrec :: ReadPrec Game
$creadListPrec :: ReadPrec [Game]
readListPrec :: ReadPrec [Game]
Read)
data GameTree
= TreeGo TreeGo
| TreeBackgammon TreeBackgammon
| TreeLinesOfAction TreeLinesOfAction
| TreeHex [(ViewerSetting, Bool)] TreeHex
| TreeOcti TreeOcti
| TreeOther GameType TreeOther
deriving (GameTree -> GameTree -> Bool
(GameTree -> GameTree -> Bool)
-> (GameTree -> GameTree -> Bool) -> Eq GameTree
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameTree -> GameTree -> Bool
== :: GameTree -> GameTree -> Bool
$c/= :: GameTree -> GameTree -> Bool
/= :: GameTree -> GameTree -> Bool
Eq, Int -> GameTree -> ShowS
[GameTree] -> ShowS
GameTree -> String
(Int -> GameTree -> ShowS)
-> (GameTree -> String) -> ([GameTree] -> ShowS) -> Show GameTree
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameTree -> ShowS
showsPrec :: Int -> GameTree -> ShowS
$cshow :: GameTree -> String
show :: GameTree -> String
$cshowList :: [GameTree] -> ShowS
showList :: [GameTree] -> ShowS
Show, ReadPrec [GameTree]
ReadPrec GameTree
Int -> ReadS GameTree
ReadS [GameTree]
(Int -> ReadS GameTree)
-> ReadS [GameTree]
-> ReadPrec GameTree
-> ReadPrec [GameTree]
-> Read GameTree
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GameTree
readsPrec :: Int -> ReadS GameTree
$creadList :: ReadS [GameTree]
readList :: ReadS [GameTree]
$creadPrec :: ReadPrec GameTree
readPrec :: ReadPrec GameTree
$creadListPrec :: ReadPrec [GameTree]
readListPrec :: ReadPrec [GameTree]
Read)
type TreeGo = Tree NodeGo
type TreeBackgammon = Tree NodeBackgammon
type TreeLinesOfAction = Tree NodeLinesOfAction
type TreeHex = Tree NodeHex
type TreeOcti = Tree NodeOcti
type TreeOther = Tree NodeOther
data GameNode move stone ruleSet extraGameInfo extraAnnotation = GameNode {
forall move stone ruleSet extraGameInfo extraAnnotation.
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Maybe (GameInfo ruleSet extraGameInfo)
gameInfo :: Maybe (GameInfo ruleSet extraGameInfo),
forall move stone ruleSet extraGameInfo extraAnnotation.
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Either (Setup stone) (Move move)
action :: Either (Setup stone) (Move move),
forall move stone ruleSet extraGameInfo extraAnnotation.
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Annotation extraAnnotation
annotation :: Annotation extraAnnotation,
forall move stone ruleSet extraGameInfo extraAnnotation.
GameNode move stone ruleSet extraGameInfo extraAnnotation -> Markup
markup :: Markup,
forall move stone ruleSet extraGameInfo extraAnnotation.
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Map String [[Word8]]
unknown :: Map String [[Word8]]
} deriving (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
(GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool)
-> Eq (GameNode move stone ruleSet extraGameInfo extraAnnotation)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall move stone ruleSet extraGameInfo extraAnnotation.
(Eq ruleSet, Eq extraGameInfo, Eq stone, Eq move,
Eq extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
$c== :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Eq ruleSet, Eq extraGameInfo, Eq stone, Eq move,
Eq extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
== :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
$c/= :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Eq ruleSet, Eq extraGameInfo, Eq stone, Eq move,
Eq extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
/= :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
Eq, Eq (GameNode move stone ruleSet extraGameInfo extraAnnotation)
Eq (GameNode move stone ruleSet extraGameInfo extraAnnotation) =>
(GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Ordering)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation)
-> Ord (GameNode move stone ruleSet extraGameInfo extraAnnotation)
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Ordering
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
Eq (GameNode move stone ruleSet extraGameInfo extraAnnotation)
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Ordering
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
$ccompare :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Ordering
compare :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Ordering
$c< :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
< :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
$c<= :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
<= :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
$c> :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
> :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
$c>= :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
>= :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> Bool
$cmax :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
max :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
$cmin :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move,
Ord extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
min :: GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
Ord, Int
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> ShowS
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> ShowS
GameNode move stone ruleSet extraGameInfo extraAnnotation -> String
(Int
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> ShowS)
-> (GameNode move stone ruleSet extraGameInfo extraAnnotation
-> String)
-> ([GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> ShowS)
-> Show (GameNode move stone ruleSet extraGameInfo extraAnnotation)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall move stone ruleSet extraGameInfo extraAnnotation.
(Show ruleSet, Show extraGameInfo, Show stone, Show move,
Show extraAnnotation) =>
Int
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> ShowS
forall move stone ruleSet extraGameInfo extraAnnotation.
(Show ruleSet, Show extraGameInfo, Show stone, Show move,
Show extraAnnotation) =>
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> ShowS
forall move stone ruleSet extraGameInfo extraAnnotation.
(Show ruleSet, Show extraGameInfo, Show stone, Show move,
Show extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation -> String
$cshowsPrec :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Show ruleSet, Show extraGameInfo, Show stone, Show move,
Show extraAnnotation) =>
Int
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> ShowS
showsPrec :: Int
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
-> ShowS
$cshow :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Show ruleSet, Show extraGameInfo, Show stone, Show move,
Show extraAnnotation) =>
GameNode move stone ruleSet extraGameInfo extraAnnotation -> String
show :: GameNode move stone ruleSet extraGameInfo extraAnnotation -> String
$cshowList :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Show ruleSet, Show extraGameInfo, Show stone, Show move,
Show extraAnnotation) =>
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> ShowS
showList :: [GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> ShowS
Show, ReadPrec
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
ReadPrec
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
Int
-> ReadS
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
ReadS [GameNode move stone ruleSet extraGameInfo extraAnnotation]
(Int
-> ReadS
(GameNode move stone ruleSet extraGameInfo extraAnnotation))
-> ReadS
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> ReadPrec
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
-> ReadPrec
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
-> Read (GameNode move stone ruleSet extraGameInfo extraAnnotation)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
ReadPrec
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
ReadPrec
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
Int
-> ReadS
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
ReadS [GameNode move stone ruleSet extraGameInfo extraAnnotation]
$creadsPrec :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
Int
-> ReadS
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
readsPrec :: Int
-> ReadS
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
$creadList :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
ReadS [GameNode move stone ruleSet extraGameInfo extraAnnotation]
readList :: ReadS [GameNode move stone ruleSet extraGameInfo extraAnnotation]
$creadPrec :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
ReadPrec
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
readPrec :: ReadPrec
(GameNode move stone ruleSet extraGameInfo extraAnnotation)
$creadListPrec :: forall move stone ruleSet extraGameInfo extraAnnotation.
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone,
Read move, Read extraAnnotation) =>
ReadPrec
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
readListPrec :: ReadPrec
[GameNode move stone ruleSet extraGameInfo extraAnnotation]
Read)
emptyGameNode :: GameNode move stone ruleSet extraGameInfo ()
emptyGameNode :: forall move stone ruleSet extraGameInfo.
GameNode move stone ruleSet extraGameInfo ()
emptyGameNode = Maybe (GameInfo ruleSet extraGameInfo)
-> Either (Setup stone) (Move move)
-> Annotation ()
-> Markup
-> Map String [[Word8]]
-> GameNode move stone ruleSet extraGameInfo ()
forall move stone ruleSet extraGameInfo extraAnnotation.
Maybe (GameInfo ruleSet extraGameInfo)
-> Either (Setup stone) (Move move)
-> Annotation extraAnnotation
-> Markup
-> Map String [[Word8]]
-> GameNode move stone ruleSet extraGameInfo extraAnnotation
GameNode Maybe (GameInfo ruleSet extraGameInfo)
forall a. Maybe a
Nothing (Setup stone -> Either (Setup stone) (Move move)
forall a b. a -> Either a b
Left Setup stone
forall stone. Setup stone
emptySetup) Annotation ()
emptyAnnotation Markup
emptyMarkup Map String [[Word8]]
forall k a. Map k a
Map.empty
type NodeGo = GameNode MoveGo Point RuleSetGo GameInfoGo AnnotationGo
type NodeBackgammon = GameNode () () RuleSetBackgammon GameInfoBackgammon ()
type NodeLinesOfAction = GameNode () () Void GameInfoLinesOfAction ()
type NodeHex = GameNode () () Void GameInfoHex ()
type NodeOcti = GameNode () () RuleSetOcti GameInfoOcti ()
type NodeOther = GameNode [Word8] [Word8] Void () ()