Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Types used to represent an SGF tree. Whenever a data type is used by exactly one other data type, there will be a "see also" link to its containing type.
Synopsis
- data Game = Game {
- application :: Maybe (Application, Version)
- variationType :: Maybe (VariationType, AutoMarkup)
- size :: Maybe (Integer, Integer)
- tree :: GameTree
- data GameTree
- data GameNode move stone ruleSet extraGameInfo extraAnnotation = GameNode {}
- data Move move = Move {}
- data Setup stone = Setup {}
- data Annotation extra = Annotation {}
- data Markup = Markup {}
- data GameInfo ruleSet extra = GameInfo {}
- data GameInfoType
- emptyGameNode :: GameNode move stone ruleSet extraGameInfo ()
- emptyMove :: Move move
- emptySetup :: Setup stone
- emptyGameInfo :: GameInfo ruleSet ()
- emptyAnnotation :: Annotation ()
- emptyMarkup :: Markup
- type NodeGo = GameNode MoveGo Point RuleSetGo GameInfoGo AnnotationGo
- data MoveGo
- data RuleSetGo
- = AGA
- | GOE
- | Chinese
- | Japanese
- | NewZealand
- data GameInfoGo = GameInfoGo {}
- type AnnotationGo = Map Color (Set Point)
- type NodeBackgammon = GameNode () () RuleSetBackgammon GameInfoBackgammon ()
- data RuleSetBackgammon
- type GameInfoBackgammon = [MatchInfo]
- data MatchInfo
- type NodeLinesOfAction = GameNode () () Void GameInfoLinesOfAction ()
- data GameInfoLinesOfAction = GameInfoLinesOfAction {}
- data InitialPosition
- data InitialPlacement
- type NodeHex = GameNode () () Void GameInfoHex ()
- type GameInfoHex = Bool
- data ViewerSetting
- type NodeOcti = GameNode () () RuleSetOcti GameInfoOcti ()
- data RuleSetOcti = OctiRuleSet MajorVariation (Set MinorVariation)
- data GameInfoOcti = GameInfoOcti {
- squaresWhite :: Set Point
- squaresBlack :: Set Point
- prongs :: Integer
- reserve :: Integer
- superProngs :: Integer
- data MajorVariation
- data MinorVariation
- type NodeOther = GameNode [Word8] [Word8] Void () ()
- type Collection = [Game]
- type Point = (Integer, Integer)
- type Application = String
- type Version = String
- type AutoMarkup = Bool
- 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 Color
- data RankScale
- data Emphasis
- data Certainty
- data FuzzyBool
- data GameType
- = Go
- | Othello
- | Chess
- | Gomoku
- | NineMen'sMorris
- | Backgammon
- | ChineseChess
- | Shogi
- | LinesOfAction
- | Ataxx
- | Hex
- | Jungle
- | Neutron
- | Philosopher'sFootball
- | 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
- data Judgment
- data Quality
- data Mark
- data Numbering
- data VariationType
- data FigureFlag
- data WinType
- data GameResult
- data Rank
- data RuleSet a
- = Known !a
- | OtherRuleSet String
- data Round
- data PartialDate
- data Figure
- data Void
Game type
See also Collection
.
Game | |
|
See also Game
.
TreeGo TreeGo | |
TreeBackgammon TreeBackgammon | |
TreeLinesOfAction TreeLinesOfAction | |
TreeHex [(ViewerSetting, Bool)] TreeHex | Applications can store and read settings in the first argument here. This got totally shoehorned into the spec by some particular viewer, I'm sure, but it's in the spec now, so there we go. See also http://www.red-bean.com/sgf/hex.html#IS |
TreeOcti TreeOcti | |
TreeOther GameType TreeOther |
data GameNode move stone ruleSet extraGameInfo extraAnnotation Source #
See also GameTree
.
GameNode | |
|
Instances
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone, Read move, Read extraAnnotation) => Read (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS (GameNode move stone ruleSet extraGameInfo extraAnnotation) # readList :: ReadS [GameNode move stone ruleSet extraGameInfo extraAnnotation] # readPrec :: ReadPrec (GameNode move stone ruleSet extraGameInfo extraAnnotation) # readListPrec :: ReadPrec [GameNode move stone ruleSet extraGameInfo extraAnnotation] # | |
(Show ruleSet, Show extraGameInfo, Show stone, Show move, Show extraAnnotation) => Show (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # | |
(Eq ruleSet, Eq extraGameInfo, Eq stone, Eq move, Eq extraAnnotation) => Eq (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # | |
(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move, Ord extraAnnotation) => Ord (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # | |
Defined in Data.SGF.Types compare :: 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 # max :: 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 # |
See also GameNode
.
Move | |
|
See also GameNode
. Setup
nodes are distinct from Move
nodes in that
they need not correspond to any natural part of the game, and game rules
(e.g. for capture) are not applied after executing Setup
nodes. They can
be used for any non-standard changes to the game board or to create illegal
board positions. The locations specified in the addBlack
, addWhite
, and
remove
fields must be pairwise disjoint.
Setup | |
|
Instances
(Read stone, Ord stone) => Read (Setup stone) Source # | |
Show stone => Show (Setup stone) Source # | |
Eq stone => Eq (Setup stone) Source # | |
Ord stone => Ord (Setup stone) Source # | |
Defined in Data.SGF.Types |
data Annotation extra Source #
See also GameNode
.
Annotation | |
|
Instances
See also GameNode
. Presumably, no arrow in the arrows
field should
exactly overlap a line specified in the lines
field; however, this is not
explicitly made illegal by the SGF spec. Note that some fields are marked
"inherit". These inheritances are not explicitly tracked; Nothing
values
indicate that the correct interpretation depends on the node's ancestors, or
on the default if no ancestor has a Just
value in this field.
Markup | |
|
data GameInfo ruleSet extra Source #
See also GameNode
. Each individual game may have at most one node with
associated game info. If it has such a node, it must occur at the first node
where that game is distinguishable from all of the other games in the tree.
GameInfo | |
|
Instances
(Read ruleSet, Read extra) => Read (GameInfo ruleSet extra) Source # | |
(Show ruleSet, Show extra) => Show (GameInfo ruleSet extra) Source # | |
(Eq ruleSet, Eq extra) => Eq (GameInfo ruleSet extra) Source # | |
(Ord ruleSet, Ord extra) => Ord (GameInfo ruleSet extra) Source # | |
Defined in Data.SGF.Types compare :: 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 # max :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> GameInfo ruleSet extra # min :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> GameInfo ruleSet extra # |
data GameInfoType Source #
TeamName Color | See also the BT and WT properties at http://www.red-bean.com/sgf/properties.html#BT |
PlayerName Color | See also the PB and PW properties at http://www.red-bean.com/sgf/properties.html#PB |
Annotator | The name of the person who annotated the game. See also http://www.red-bean.com/sgf/properties.html#AN |
Source | The name of the source, e.g. the title of the book this game came from. See also http://www.red-bean.com/sgf/properties.html#SO |
User | The name of the person or program who entered the game. See also http://www.red-bean.com/sgf/properties.html#US |
Copyright | |
Context | Background information or a summary of the game. See also http://www.red-bean.com/sgf/properties.html#GC |
Location | Where the game was played. See also http://www.red-bean.com/sgf/properties.html#PC |
Event | The name of the event or tournament at which the game occurred.
Additional information about the game (e.g. that it was in the finals)
should appear in the |
GameName | An easily-remembered moniker for the game. See also http://www.red-bean.com/sgf/properties.html#GN |
Opening | A description of the opening moves using the game's vernacular. See also http://www.red-bean.com/sgf/properties.html#ON |
Overtime | The overtime rules. See also http://www.red-bean.com/sgf/properties.html#OT |
Instances
emptyGameNode :: GameNode move stone ruleSet extraGameInfo () Source #
emptySetup :: Setup stone Source #
emptyGameInfo :: GameInfo ruleSet () Source #
emptyAnnotation :: Annotation () Source #
emptyMarkup :: Markup Source #
Game-specific types
Go
See also RuleSet
, GameInfo
, and
http://red-bean.com/sgf/properties.html#RU
AGA | American Go Association rules |
GOE | Ing rules |
Chinese | |
Japanese | |
NewZealand |
Instances
Bounded RuleSetGo Source # | |
Enum RuleSetGo Source # | |
Defined in Data.SGF.Types succ :: RuleSetGo -> RuleSetGo # pred :: RuleSetGo -> RuleSetGo # fromEnum :: RuleSetGo -> Int # enumFrom :: RuleSetGo -> [RuleSetGo] # enumFromThen :: RuleSetGo -> RuleSetGo -> [RuleSetGo] # enumFromTo :: RuleSetGo -> RuleSetGo -> [RuleSetGo] # enumFromThenTo :: RuleSetGo -> RuleSetGo -> RuleSetGo -> [RuleSetGo] # | |
Read RuleSetGo Source # | |
Show RuleSetGo Source # | |
Eq RuleSetGo Source # | |
Ord RuleSetGo Source # | |
Defined in Data.SGF.Types |
data GameInfoGo Source #
See also NodeGo
and the otherGameInfo
field of GameInfo
.
Instances
Read GameInfoGo Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS GameInfoGo # readList :: ReadS [GameInfoGo] # readPrec :: ReadPrec GameInfoGo # readListPrec :: ReadPrec [GameInfoGo] # | |
Show GameInfoGo Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> GameInfoGo -> ShowS # show :: GameInfoGo -> String # showList :: [GameInfoGo] -> ShowS # | |
Eq GameInfoGo Source # | |
Defined in Data.SGF.Types (==) :: GameInfoGo -> GameInfoGo -> Bool # (/=) :: GameInfoGo -> GameInfoGo -> Bool # | |
Ord GameInfoGo Source # | |
Defined in Data.SGF.Types compare :: GameInfoGo -> GameInfoGo -> Ordering # (<) :: GameInfoGo -> GameInfoGo -> Bool # (<=) :: GameInfoGo -> GameInfoGo -> Bool # (>) :: GameInfoGo -> GameInfoGo -> Bool # (>=) :: GameInfoGo -> GameInfoGo -> Bool # max :: GameInfoGo -> GameInfoGo -> GameInfoGo # min :: GameInfoGo -> GameInfoGo -> GameInfoGo # |
type AnnotationGo = Map Color (Set Point) Source #
See also NodeGo
and the otherAnnotation
field of Annotation
. This
specifies which points are considered territory for each player. See also
the TB and TW properties at http://red-bean.com/sgf/go.html#TB
Backgammon
type NodeBackgammon = GameNode () () RuleSetBackgammon GameInfoBackgammon () Source #
data RuleSetBackgammon Source #
See also RuleSet
, GameInfo
, and
http://red-bean.com/sgf/backgammon.html#RU
Crawford | The Crawford rule is being used. |
CrawfordGame | This game is the Crawford game. |
Jacoby | The Jacoby rule is being used. |
Instances
type GameInfoBackgammon = [MatchInfo] Source #
See also NodeBackgammon
and the otherGameInfo
field of GameInfo
. An
empty list indicates that no match information was specified. The order of
the list is not significant, and there should be only one value of any given
kind of MatchInfo
. See also http://red-bean.com/sgf/backgammon.html#MI
Length Integer | The number of points in this match. |
GameNumber Integer | The (1-indexed) number of the game within this match. |
StartScore Color Integer | The score at the beginning of the game. |
OtherMatchInfo String String | An unknown piece of match information. |
Lines of Action
type NodeLinesOfAction = GameNode () () Void GameInfoLinesOfAction () Source #
data GameInfoLinesOfAction Source #
See also NodeLinesOfAction
and the otherGameInfo
field of GameInfo
.
GameInfoLinesOfAction | |
|
Instances
Read GameInfoLinesOfAction Source # | |
Defined in Data.SGF.Types | |
Show GameInfoLinesOfAction Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> GameInfoLinesOfAction -> ShowS # show :: GameInfoLinesOfAction -> String # showList :: [GameInfoLinesOfAction] -> ShowS # | |
Eq GameInfoLinesOfAction Source # | |
Defined in Data.SGF.Types (==) :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool # (/=) :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool # | |
Ord GameInfoLinesOfAction Source # | |
Defined in Data.SGF.Types compare :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Ordering # (<) :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool # (<=) :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool # (>) :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool # (>=) :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> Bool # max :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> GameInfoLinesOfAction # min :: GameInfoLinesOfAction -> GameInfoLinesOfAction -> GameInfoLinesOfAction # |
data InitialPosition Source #
See also GameInfoLinesOfAction
.
Instances
data InitialPlacement Source #
See also GameInfoLinesOfAction
.
Instances
Hex
type GameInfoHex = Bool Source #
See also NodeHex
and the otherGameInfo
field of GameInfo
. The
specification says that trees representing Hex games will mark which
position the viewer should initially show by setting this field to True
.
I think this is probably an error in the specification; there is an obvious
conflict between the requirement to put all game information at the first
node where a game is uniquely identifiable and the requirement to have a
game-information property at the location you want to view first (whenever
these two nodes are not the same node, of course). For this reason, Hex
game trees may have paths containing two nodes whose game information is not
Nothing
. See also http://www.red-bean.com/sgf/hex.html#IP
data ViewerSetting Source #
See also GameTree
and http://www.red-bean.com/sgf/hex.html#IS
Tried | Identify future moves that have been tried? |
Marked | Show good/bad move markings? |
LastMove | Identify the last cell played? |
Headings | Display column/row headings? |
Lock | Lock the game against new moves? |
Instances
Octi
For Octi, Black
always refers to the first player and White
always
refers to the second player, regardless of the colors of the actual pieces
used by the first and second players.
type NodeOcti = GameNode () () RuleSetOcti GameInfoOcti () Source #
data RuleSetOcti Source #
See also RuleSet
, GameInfo
, and http://red-bean.com/sgf/octi.html#RU
Instances
Read RuleSetOcti Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS RuleSetOcti # readList :: ReadS [RuleSetOcti] # readPrec :: ReadPrec RuleSetOcti # readListPrec :: ReadPrec [RuleSetOcti] # | |
Show RuleSetOcti Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> RuleSetOcti -> ShowS # show :: RuleSetOcti -> String # showList :: [RuleSetOcti] -> ShowS # | |
Eq RuleSetOcti Source # | |
Defined in Data.SGF.Types (==) :: RuleSetOcti -> RuleSetOcti -> Bool # (/=) :: RuleSetOcti -> RuleSetOcti -> Bool # | |
Ord RuleSetOcti Source # | |
Defined in Data.SGF.Types compare :: RuleSetOcti -> RuleSetOcti -> Ordering # (<) :: RuleSetOcti -> RuleSetOcti -> Bool # (<=) :: RuleSetOcti -> RuleSetOcti -> Bool # (>) :: RuleSetOcti -> RuleSetOcti -> Bool # (>=) :: RuleSetOcti -> RuleSetOcti -> Bool # max :: RuleSetOcti -> RuleSetOcti -> RuleSetOcti # min :: RuleSetOcti -> RuleSetOcti -> RuleSetOcti # |
data GameInfoOcti Source #
See also NodeOcti
and the otherGameInfo
field of GameInfo
.
GameInfoOcti | |
|
Instances
Read GameInfoOcti Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS GameInfoOcti # readList :: ReadS [GameInfoOcti] # | |
Show GameInfoOcti Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> GameInfoOcti -> ShowS # show :: GameInfoOcti -> String # showList :: [GameInfoOcti] -> ShowS # | |
Eq GameInfoOcti Source # | |
Defined in Data.SGF.Types (==) :: GameInfoOcti -> GameInfoOcti -> Bool # (/=) :: GameInfoOcti -> GameInfoOcti -> Bool # | |
Ord GameInfoOcti Source # | |
Defined in Data.SGF.Types compare :: GameInfoOcti -> GameInfoOcti -> Ordering # (<) :: GameInfoOcti -> GameInfoOcti -> Bool # (<=) :: GameInfoOcti -> GameInfoOcti -> Bool # (>) :: GameInfoOcti -> GameInfoOcti -> Bool # (>=) :: GameInfoOcti -> GameInfoOcti -> Bool # max :: GameInfoOcti -> GameInfoOcti -> GameInfoOcti # min :: GameInfoOcti -> GameInfoOcti -> GameInfoOcti # |
data MajorVariation Source #
See also RuleSetOcti
.
Instances
data MinorVariation Source #
See also RuleSetOcti
.
Instances
Read MinorVariation Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS MinorVariation # readList :: ReadS [MinorVariation] # | |
Show MinorVariation Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> MinorVariation -> ShowS # show :: MinorVariation -> String # showList :: [MinorVariation] -> ShowS # | |
Eq MinorVariation Source # | |
Defined in Data.SGF.Types (==) :: MinorVariation -> MinorVariation -> Bool # (/=) :: MinorVariation -> MinorVariation -> Bool # | |
Ord MinorVariation Source # | |
Defined in Data.SGF.Types compare :: MinorVariation -> MinorVariation -> Ordering # (<) :: MinorVariation -> MinorVariation -> Bool # (<=) :: MinorVariation -> MinorVariation -> Bool # (>) :: MinorVariation -> MinorVariation -> Bool # (>=) :: MinorVariation -> MinorVariation -> Bool # max :: MinorVariation -> MinorVariation -> MinorVariation # min :: MinorVariation -> MinorVariation -> MinorVariation # |
Other
Type aliases
type Collection = [Game] Source #
type Application = String Source #
See also Game
.
type AutoMarkup = Bool Source #
See also Game
.
type TreeBackgammon = Tree NodeBackgammon Source #
See also GameTree
.
type TreeLinesOfAction = Tree NodeLinesOfAction Source #
See also GameTree
.
Enumerations
See also Rank
. In addition to the standard "kyu" and "dan" ranks,
this also supports the non-standard (but common) "pro" ranks.
Instances
Bounded RankScale Source # | |
Enum RankScale Source # | |
Defined in Data.SGF.Types succ :: RankScale -> RankScale # pred :: RankScale -> RankScale # fromEnum :: RankScale -> Int # enumFrom :: RankScale -> [RankScale] # enumFromThen :: RankScale -> RankScale -> [RankScale] # enumFromTo :: RankScale -> RankScale -> [RankScale] # enumFromThenTo :: RankScale -> RankScale -> RankScale -> [RankScale] # | |
Read RankScale Source # | |
Show RankScale Source # | |
Eq RankScale Source # | |
Ord RankScale Source # | |
Defined in Data.SGF.Types |
Instances
Bounded Emphasis Source # | |
Enum Emphasis Source # | |
Read Emphasis Source # | |
Show Emphasis Source # | |
Eq Emphasis Source # | |
Ord Emphasis Source # | |
Defined in Data.SGF.Types |
See also Rank
.
Instances
Bounded Certainty Source # | |
Enum Certainty Source # | |
Defined in Data.SGF.Types succ :: Certainty -> Certainty # pred :: Certainty -> Certainty # fromEnum :: Certainty -> Int # enumFrom :: Certainty -> [Certainty] # enumFromThen :: Certainty -> Certainty -> [Certainty] # enumFromTo :: Certainty -> Certainty -> [Certainty] # enumFromThenTo :: Certainty -> Certainty -> Certainty -> [Certainty] # | |
Read Certainty Source # | |
Show Certainty Source # | |
Eq Certainty Source # | |
Ord Certainty Source # | |
Defined in Data.SGF.Types |
See also Move
.
Instances
Bounded FuzzyBool Source # | |
Enum FuzzyBool Source # | |
Defined in Data.SGF.Types succ :: FuzzyBool -> FuzzyBool # pred :: FuzzyBool -> FuzzyBool # fromEnum :: FuzzyBool -> Int # enumFrom :: FuzzyBool -> [FuzzyBool] # enumFromThen :: FuzzyBool -> FuzzyBool -> [FuzzyBool] # enumFromTo :: FuzzyBool -> FuzzyBool -> [FuzzyBool] # enumFromThenTo :: FuzzyBool -> FuzzyBool -> FuzzyBool -> [FuzzyBool] # | |
Read FuzzyBool Source # | |
Show FuzzyBool Source # | |
Eq FuzzyBool Source # | |
Ord FuzzyBool Source # | |
Defined in Data.SGF.Types |
See also GameTree
. This enumeration is used for the GM property (see
http://www.red-bean.com/sgf/properties.html#GM). The Enum instance
converts to and from the numeric game codes listed there.
Instances
Bounded GameType Source # | |
Enum GameType Source # | |
Read GameType Source # | |
Show GameType Source # | |
Eq GameType Source # | |
Ord GameType Source # | |
Defined in Data.SGF.Types |
See also Annotation
.
Instances
Bounded Judgment Source # | |
Enum Judgment Source # | |
Read Judgment Source # | |
Show Judgment Source # | |
Eq Judgment Source # | |
Ord Judgment Source # | |
Defined in Data.SGF.Types |
See also Move
.
See also Markup
. With the exception of Selected
, the constructor
names describe a shape whose outline should be shown over the given point.
Circle | |
X | |
Selected | The exact appearance of this kind of markup is not specified, though suggestions include darkening the colors on these points or inverting the colors on these points. |
Square | |
Triangle |
See also Markup
.
Unnumbered | Don't print move numbers. |
Numbered | Print move numbers as they are. |
Modulo100 | Subtract enough multiples of 100 from each move number that the first labeled move is below 100. |
Instances
Bounded Numbering Source # | |
Enum Numbering Source # | |
Defined in Data.SGF.Types succ :: Numbering -> Numbering # pred :: Numbering -> Numbering # fromEnum :: Numbering -> Int # enumFrom :: Numbering -> [Numbering] # enumFromThen :: Numbering -> Numbering -> [Numbering] # enumFromTo :: Numbering -> Numbering -> [Numbering] # enumFromThenTo :: Numbering -> Numbering -> Numbering -> [Numbering] # | |
Read Numbering Source # | |
Show Numbering Source # | |
Eq Numbering Source # | |
Ord Numbering Source # | |
Defined in Data.SGF.Types |
data VariationType Source #
See also Game
.
Instances
data FigureFlag Source #
See also Figure
.
Coordinates | Show coordinates around the edges of the board. |
Name | Show the diagram's name. |
HiddenMoves | List moves that can't be shown in the diagram as text. |
RemoveCaptures | Remove captured stones from the diagram. |
Hoshi | Show hoshi dots. |
Instances
Miscellaneous
See also GameResult
. Games that end normally use Score
if there is a
natural concept of score differential for that game and OtherWinType
if
not.
data GameResult Source #
See also GameInfo
.
Instances
Read GameResult Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS GameResult # readList :: ReadS [GameResult] # readPrec :: ReadPrec GameResult # readListPrec :: ReadPrec [GameResult] # | |
Show GameResult Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> GameResult -> ShowS # show :: GameResult -> String # showList :: [GameResult] -> ShowS # | |
Eq GameResult Source # | |
Defined in Data.SGF.Types (==) :: GameResult -> GameResult -> Bool # (/=) :: GameResult -> GameResult -> Bool # | |
Ord GameResult Source # | |
Defined in Data.SGF.Types compare :: GameResult -> GameResult -> Ordering # (<) :: GameResult -> GameResult -> Bool # (<=) :: GameResult -> GameResult -> Bool # (>) :: GameResult -> GameResult -> Bool # (>=) :: GameResult -> GameResult -> Bool # max :: GameResult -> GameResult -> GameResult # min :: GameResult -> GameResult -> GameResult # |
See also GameInfo
, especially the rankBlack
and rankWhite
fields.
The Eq
and Ord
instances are the derived ones, and should not be mistaken
for semantic equality or ordering.
Ranked Integer RankScale (Maybe Certainty) | Ranked in one of the standard ways. Most SGF generators specify
the certainty only when it is |
OtherRank String | Any rank that does not fall in the standard categories. This field must not contain newlines. |
See also GameInfo
. Typical values for the a
type variable are
RuleSetGo
, RuleSetBackgammon
, and RuleSetOcti
. For games where the
valid values of the ruleset field is not specified, the a
type variable
will be Void
to ensure that all rulesets are specified as a String
.
See also GameInfo
.
SimpleRound Integer | Only a round number is given. |
FormattedRound Integer String | Both a round number and a type, like "final", "playoff", or "league". |
OtherRound String | Round information in an unknown format. |
data PartialDate Source #
See also GameInfo
.
Instances
Read PartialDate Source # | |
Defined in Data.SGF.Types readsPrec :: Int -> ReadS PartialDate # readList :: ReadS [PartialDate] # readPrec :: ReadPrec PartialDate # readListPrec :: ReadPrec [PartialDate] # | |
Show PartialDate Source # | |
Defined in Data.SGF.Types showsPrec :: Int -> PartialDate -> ShowS # show :: PartialDate -> String # showList :: [PartialDate] -> ShowS # | |
Eq PartialDate Source # | |
Defined in Data.SGF.Types (==) :: PartialDate -> PartialDate -> Bool # (/=) :: PartialDate -> PartialDate -> Bool # | |
Ord PartialDate Source # | |
Defined in Data.SGF.Types compare :: PartialDate -> PartialDate -> Ordering # (<) :: PartialDate -> PartialDate -> Bool # (<=) :: PartialDate -> PartialDate -> Bool # (>) :: PartialDate -> PartialDate -> Bool # (>=) :: PartialDate -> PartialDate -> Bool # max :: PartialDate -> PartialDate -> PartialDate # min :: PartialDate -> PartialDate -> PartialDate # |
See also Markup
.
DefaultFigure | Unnamed figure using the application default settings. |
NamedDefaultFigure String | Named figure using the application default settings. |
NamedFigure String (FigureFlag -> Bool) | Named figure that overrides the application's figure settings. |
A type with no constructors used merely to indicate a lack of data.