sgf-0.1.3.3: SGF (Smart Game Format) parser
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.SGF.Types

Description

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

Game type

data Game Source #

See also Collection.

Constructors

Game 

Fields

Instances

Instances details
Read Game Source # 
Instance details

Defined in Data.SGF.Types

Show Game Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Game -> ShowS #

show :: Game -> String #

showList :: [Game] -> ShowS #

Eq Game Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

data GameTree Source #

See also Game.

Constructors

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 

Instances

Instances details
Read GameTree Source # 
Instance details

Defined in Data.SGF.Types

Show GameTree Source # 
Instance details

Defined in Data.SGF.Types

Eq GameTree Source # 
Instance details

Defined in Data.SGF.Types

data GameNode move stone ruleSet extraGameInfo extraAnnotation Source #

See also GameTree.

Constructors

GameNode 

Fields

  • gameInfo :: Maybe (GameInfo ruleSet extraGameInfo)

    All properties with propertytype game-info. There must be only one Just on any path within a GameTree.

  • action :: Either (Setup stone) (Move move)

    All properties with propertytype setup or move.

  • annotation :: Annotation extraAnnotation

    Positional judgments and comments (as opposed to judgments of particular moves). All properties covered in the "Node annotation" section.

  • markup :: Markup

    How a node should be displayed. All properties covered in the "Markup" and "Miscellaneous" sections.

  • unknown :: Map String [[Word8]]

    Unspecified properties. The keys in the map must contain only the characters A-Z (and must be upper-case). The values in the map may be more or less arbitrary, but any occurrence of the ASCII byte ']' must be preceded by an odd number of copies of the ASCII byte '\'. See also http://www.red-bean.com/sgf/sgf4.html#2.2

Instances

Instances details
(Ord stone, Read ruleSet, Read extraGameInfo, Read stone, Read move, Read extraAnnotation) => Read (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # 
Instance details

Defined in Data.SGF.Types

Methods

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 # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> GameNode move stone ruleSet extraGameInfo extraAnnotation -> ShowS #

show :: GameNode move stone ruleSet extraGameInfo extraAnnotation -> String #

showList :: [GameNode move stone ruleSet extraGameInfo extraAnnotation] -> ShowS #

(Eq ruleSet, Eq extraGameInfo, Eq stone, Eq move, Eq extraAnnotation) => Eq (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # 
Instance details

Defined in Data.SGF.Types

Methods

(==) :: 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 #

(Ord ruleSet, Ord extraGameInfo, Ord stone, Ord move, Ord extraAnnotation) => Ord (GameNode move stone ruleSet extraGameInfo extraAnnotation) Source # 
Instance details

Defined in Data.SGF.Types

Methods

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 #

data Move move Source #

See also GameNode.

Constructors

Move 

Fields

Instances

Instances details
Read move => Read (Move move) Source # 
Instance details

Defined in Data.SGF.Types

Methods

readsPrec :: Int -> ReadS (Move move) #

readList :: ReadS [Move move] #

readPrec :: ReadPrec (Move move) #

readListPrec :: ReadPrec [Move move] #

Show move => Show (Move move) Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Move move -> ShowS #

show :: Move move -> String #

showList :: [Move move] -> ShowS #

Eq move => Eq (Move move) Source # 
Instance details

Defined in Data.SGF.Types

Methods

(==) :: Move move -> Move move -> Bool #

(/=) :: Move move -> Move move -> Bool #

Ord move => Ord (Move move) Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: 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 #

max :: Move move -> Move move -> Move move #

min :: Move move -> Move move -> Move move #

data Setup stone Source #

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.

Constructors

Setup 

Fields

Instances

Instances details
(Read stone, Ord stone) => Read (Setup stone) Source # 
Instance details

Defined in Data.SGF.Types

Methods

readsPrec :: Int -> ReadS (Setup stone) #

readList :: ReadS [Setup stone] #

readPrec :: ReadPrec (Setup stone) #

readListPrec :: ReadPrec [Setup stone] #

Show stone => Show (Setup stone) Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Setup stone -> ShowS #

show :: Setup stone -> String #

showList :: [Setup stone] -> ShowS #

Eq stone => Eq (Setup stone) Source # 
Instance details

Defined in Data.SGF.Types

Methods

(==) :: Setup stone -> Setup stone -> Bool #

(/=) :: Setup stone -> Setup stone -> Bool #

Ord stone => Ord (Setup stone) Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: 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 #

max :: Setup stone -> Setup stone -> Setup stone #

min :: Setup stone -> Setup stone -> Setup stone #

data Annotation extra Source #

See also GameNode.

Constructors

Annotation 

Fields

Instances

Instances details
Read extra => Read (Annotation extra) Source # 
Instance details

Defined in Data.SGF.Types

Show extra => Show (Annotation extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Annotation extra -> ShowS #

show :: Annotation extra -> String #

showList :: [Annotation extra] -> ShowS #

Eq extra => Eq (Annotation extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

(==) :: Annotation extra -> Annotation extra -> Bool #

(/=) :: Annotation extra -> Annotation extra -> Bool #

Ord extra => Ord (Annotation extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: 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 #

max :: Annotation extra -> Annotation extra -> Annotation extra #

min :: Annotation extra -> Annotation extra -> Annotation extra #

data Markup Source #

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.

Constructors

Markup 

Fields

Instances

Instances details
Read Markup Source # 
Instance details

Defined in Data.SGF.Types

Show Markup Source # 
Instance details

Defined in Data.SGF.Types

Eq Markup Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Markup Source # 
Instance details

Defined in Data.SGF.Types

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.

Constructors

GameInfo 

Fields

Instances

Instances details
(Read ruleSet, Read extra) => Read (GameInfo ruleSet extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

readsPrec :: Int -> ReadS (GameInfo ruleSet extra) #

readList :: ReadS [GameInfo ruleSet extra] #

readPrec :: ReadPrec (GameInfo ruleSet extra) #

readListPrec :: ReadPrec [GameInfo ruleSet extra] #

(Show ruleSet, Show extra) => Show (GameInfo ruleSet extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> GameInfo ruleSet extra -> ShowS #

show :: GameInfo ruleSet extra -> String #

showList :: [GameInfo ruleSet extra] -> ShowS #

(Eq ruleSet, Eq extra) => Eq (GameInfo ruleSet extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

(==) :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool #

(/=) :: GameInfo ruleSet extra -> GameInfo ruleSet extra -> Bool #

(Ord ruleSet, Ord extra) => Ord (GameInfo ruleSet extra) Source # 
Instance details

Defined in Data.SGF.Types

Methods

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 #

See also GameInfo, especially the freeform field.

Constructors

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

See also http://www.red-bean.com/sgf/properties.html#CP

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 round field, not here. See also http://www.red-bean.com/sgf/properties.html#EV

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

Instances details
Bounded GameInfoType Source # 
Instance details

Defined in Data.SGF.Types

Enum GameInfoType Source # 
Instance details

Defined in Data.SGF.Types

Read GameInfoType Source # 
Instance details

Defined in Data.SGF.Types

Show GameInfoType Source # 
Instance details

Defined in Data.SGF.Types

Eq GameInfoType Source # 
Instance details

Defined in Data.SGF.Types

Ord GameInfoType Source # 
Instance details

Defined in Data.SGF.Types

emptyGameNode :: GameNode move stone ruleSet extraGameInfo () Source #

Game-specific types

Go

data MoveGo Source #

See also NodeGo and Game.

Constructors

Pass 
Play Point 

Instances

Instances details
Read MoveGo Source # 
Instance details

Defined in Data.SGF.Types

Show MoveGo Source # 
Instance details

Defined in Data.SGF.Types

Eq MoveGo Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord MoveGo Source # 
Instance details

Defined in Data.SGF.Types

data RuleSetGo Source #

Constructors

AGA

American Go Association rules

GOE

Ing rules

Chinese 
Japanese 
NewZealand 

data GameInfoGo Source #

See also NodeGo and the otherGameInfo field of GameInfo.

Constructors

GameInfoGo 

Fields

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

data RuleSetBackgammon Source #

Constructors

Crawford

The Crawford rule is being used.

CrawfordGame

This game is the Crawford game.

Jacoby

The Jacoby rule is being used.

Instances

Instances details
Bounded RuleSetBackgammon Source # 
Instance details

Defined in Data.SGF.Types

Enum RuleSetBackgammon Source # 
Instance details

Defined in Data.SGF.Types

Read RuleSetBackgammon Source # 
Instance details

Defined in Data.SGF.Types

Show RuleSetBackgammon Source # 
Instance details

Defined in Data.SGF.Types

Eq RuleSetBackgammon Source # 
Instance details

Defined in Data.SGF.Types

Ord RuleSetBackgammon Source # 
Instance details

Defined in Data.SGF.Types

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

data MatchInfo Source #

Constructors

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

data GameInfoLinesOfAction Source #

See also NodeLinesOfAction and the otherGameInfo field of GameInfo.

Constructors

GameInfoLinesOfAction 

Fields

data InitialPosition Source #

Constructors

Beginning 
End 

Instances

Instances details
Bounded InitialPosition Source # 
Instance details

Defined in Data.SGF.Types

Enum InitialPosition Source # 
Instance details

Defined in Data.SGF.Types

Read InitialPosition Source # 
Instance details

Defined in Data.SGF.Types

Show InitialPosition Source # 
Instance details

Defined in Data.SGF.Types

Eq InitialPosition Source # 
Instance details

Defined in Data.SGF.Types

Ord InitialPosition Source # 
Instance details

Defined in Data.SGF.Types

data InitialPlacement Source #

Instances

Instances details
Bounded InitialPlacement Source # 
Instance details

Defined in Data.SGF.Types

Enum InitialPlacement Source # 
Instance details

Defined in Data.SGF.Types

Read InitialPlacement Source # 
Instance details

Defined in Data.SGF.Types

Show InitialPlacement Source # 
Instance details

Defined in Data.SGF.Types

Eq InitialPlacement Source # 
Instance details

Defined in Data.SGF.Types

Ord InitialPlacement Source # 
Instance details

Defined in Data.SGF.Types

Hex

type NodeHex = GameNode () () Void GameInfoHex () Source #

See also GameTree and Game.

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 #

Constructors

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

Instances details
Bounded ViewerSetting Source # 
Instance details

Defined in Data.SGF.Types

Enum ViewerSetting Source # 
Instance details

Defined in Data.SGF.Types

Read ViewerSetting Source # 
Instance details

Defined in Data.SGF.Types

Show ViewerSetting Source # 
Instance details

Defined in Data.SGF.Types

Eq ViewerSetting Source # 
Instance details

Defined in Data.SGF.Types

Ord ViewerSetting Source # 
Instance details

Defined in Data.SGF.Types

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.

data GameInfoOcti Source #

See also NodeOcti and the otherGameInfo field of GameInfo.

Constructors

GameInfoOcti 

Fields

data MajorVariation Source #

See also RuleSetOcti.

Constructors

Full 
Fast 
Kids 

Instances

Instances details
Bounded MajorVariation Source # 
Instance details

Defined in Data.SGF.Types

Enum MajorVariation Source # 
Instance details

Defined in Data.SGF.Types

Read MajorVariation Source # 
Instance details

Defined in Data.SGF.Types

Show MajorVariation Source # 
Instance details

Defined in Data.SGF.Types

Eq MajorVariation Source # 
Instance details

Defined in Data.SGF.Types

Ord MajorVariation Source # 
Instance details

Defined in Data.SGF.Types

Other

type NodeOther = GameNode [Word8] [Word8] Void () () Source #

See also GameTree and Game.

Type aliases

type Point = (Integer, Integer) Source #

0-indexed x/y coordinates that start at the top left

type Application = String Source #

See also Game.

type Version = String Source #

See also Game.

type AutoMarkup = Bool Source #

See also Game.

type TreeGo = Tree NodeGo Source #

See also GameTree.

Enumerations

data Color Source #

Constructors

Black 
White 

Instances

Instances details
Bounded Color Source # 
Instance details

Defined in Data.SGF.Types

Enum Color Source # 
Instance details

Defined in Data.SGF.Types

Read Color Source # 
Instance details

Defined in Data.SGF.Types

Show Color Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Eq Color Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Color Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

data RankScale Source #

See also Rank. In addition to the standard "kyu" and "dan" ranks, this also supports the non-standard (but common) "pro" ranks.

Constructors

Kyu 
Dan 
Pro 

data Certainty Source #

See also Rank.

Constructors

Uncertain 
Certain 

data FuzzyBool Source #

See also Move.

Constructors

Possibly 
Definitely 

data GameType Source #

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.

data Judgment Source #

See also Annotation.

data Quality Source #

See also Move.

Instances

Instances details
Read Quality Source # 
Instance details

Defined in Data.SGF.Types

Show Quality Source # 
Instance details

Defined in Data.SGF.Types

Eq Quality Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Quality Source # 
Instance details

Defined in Data.SGF.Types

data Mark Source #

See also Markup. With the exception of Selected, the constructor names describe a shape whose outline should be shown over the given point.

Constructors

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 

Instances

Instances details
Bounded Mark Source # 
Instance details

Defined in Data.SGF.Types

Enum Mark Source # 
Instance details

Defined in Data.SGF.Types

Methods

succ :: Mark -> Mark #

pred :: Mark -> Mark #

toEnum :: Int -> Mark #

fromEnum :: Mark -> Int #

enumFrom :: Mark -> [Mark] #

enumFromThen :: Mark -> Mark -> [Mark] #

enumFromTo :: Mark -> Mark -> [Mark] #

enumFromThenTo :: Mark -> Mark -> Mark -> [Mark] #

Read Mark Source # 
Instance details

Defined in Data.SGF.Types

Show Mark Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Mark -> ShowS #

show :: Mark -> String #

showList :: [Mark] -> ShowS #

Eq Mark Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Mark Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: Mark -> Mark -> Ordering #

(<) :: Mark -> Mark -> Bool #

(<=) :: Mark -> Mark -> Bool #

(>) :: Mark -> Mark -> Bool #

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

max :: Mark -> Mark -> Mark #

min :: Mark -> Mark -> Mark #

data Numbering Source #

See also Markup.

Constructors

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.

data VariationType Source #

See also Game.

Constructors

Children

Variations are stored in child nodes.

Siblings

Variations are stored in sibling nodes.

Instances

Instances details
Bounded VariationType Source # 
Instance details

Defined in Data.SGF.Types

Enum VariationType Source # 
Instance details

Defined in Data.SGF.Types

Read VariationType Source # 
Instance details

Defined in Data.SGF.Types

Show VariationType Source # 
Instance details

Defined in Data.SGF.Types

Eq VariationType Source # 
Instance details

Defined in Data.SGF.Types

Ord VariationType Source # 
Instance details

Defined in Data.SGF.Types

data FigureFlag Source #

See also Figure.

Constructors

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

Instances details
Bounded FigureFlag Source # 
Instance details

Defined in Data.SGF.Types

Enum FigureFlag Source # 
Instance details

Defined in Data.SGF.Types

Read FigureFlag Source # 
Instance details

Defined in Data.SGF.Types

Show FigureFlag Source # 
Instance details

Defined in Data.SGF.Types

Eq FigureFlag Source # 
Instance details

Defined in Data.SGF.Types

Ord FigureFlag Source # 
Instance details

Defined in Data.SGF.Types

Miscellaneous

data WinType Source #

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.

Instances

Instances details
Read WinType Source # 
Instance details

Defined in Data.SGF.Types

Show WinType Source # 
Instance details

Defined in Data.SGF.Types

Eq WinType Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord WinType Source # 
Instance details

Defined in Data.SGF.Types

data GameResult Source #

See also GameInfo.

Constructors

Draw 
Void 
Unknown 
Win Color WinType

The first argument is the color of the winner.

data Rank Source #

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.

Constructors

Ranked Integer RankScale (Maybe Certainty)

Ranked in one of the standard ways. Most SGF generators specify the certainty only when it is Uncertain. Therefore, it may be reasonable to treat Nothing and Just Certain identically.

OtherRank String

Any rank that does not fall in the standard categories. This field must not contain newlines.

Instances

Instances details
Read Rank Source # 
Instance details

Defined in Data.SGF.Types

Show Rank Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Eq Rank Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Rank Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: Rank -> Rank -> Ordering #

(<) :: Rank -> Rank -> Bool #

(<=) :: Rank -> Rank -> Bool #

(>) :: Rank -> Rank -> Bool #

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

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

data RuleSet a Source #

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.

Constructors

Known !a 
OtherRuleSet String 

Instances

Instances details
Read a => Read (RuleSet a) Source # 
Instance details

Defined in Data.SGF.Types

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

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> RuleSet a -> ShowS #

show :: RuleSet a -> String #

showList :: [RuleSet a] -> ShowS #

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

Defined in Data.SGF.Types

Methods

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

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

Ord a => Ord (RuleSet a) Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: 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 #

max :: RuleSet a -> RuleSet a -> RuleSet a #

min :: RuleSet a -> RuleSet a -> RuleSet a #

data Round Source #

See also GameInfo.

Constructors

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.

Instances

Instances details
Read Round Source # 
Instance details

Defined in Data.SGF.Types

Show Round Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Round -> ShowS #

show :: Round -> String #

showList :: [Round] -> ShowS #

Eq Round Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Round Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: Round -> Round -> Ordering #

(<) :: Round -> Round -> Bool #

(<=) :: Round -> Round -> Bool #

(>) :: Round -> Round -> Bool #

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

max :: Round -> Round -> Round #

min :: Round -> Round -> Round #

data Figure Source #

See also Markup.

Constructors

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.

Instances

Instances details
Read Figure Source # 
Instance details

Defined in Data.SGF.Types

Show Figure Source # 
Instance details

Defined in Data.SGF.Types

Eq Figure Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Figure Source # 
Instance details

Defined in Data.SGF.Types

data Void Source #

A type with no constructors used merely to indicate a lack of data.

Instances

Instances details
Read Void Source # 
Instance details

Defined in Data.SGF.Types

Show Void Source # 
Instance details

Defined in Data.SGF.Types

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Eq Void Source # 
Instance details

Defined in Data.SGF.Types

Methods

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

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

Ord Void Source # 
Instance details

Defined in Data.SGF.Types

Methods

compare :: Void -> Void -> Ordering #

(<) :: Void -> Void -> Bool #

(<=) :: Void -> Void -> Bool #

(>) :: Void -> Void -> Bool #

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

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Orphan instances

(Bounded k, Enum k, Ord k, Read k, Read v) => Read (k -> v) Source # 
Instance details

Methods

readsPrec :: Int -> ReadS (k -> v) #

readList :: ReadS [k -> v] #

readPrec :: ReadPrec (k -> v) #

readListPrec :: ReadPrec [k -> v] #

(Bounded k, Enum k, Ord k, Show k, Show v) => Show (k -> v) Source # 
Instance details

Methods

showsPrec :: Int -> (k -> v) -> ShowS #

show :: (k -> v) -> String #

showList :: [k -> v] -> ShowS #

(Bounded k, Enum k, Ord k, Eq v) => Eq (k -> v) Source # 
Instance details

Methods

(==) :: (k -> v) -> (k -> v) -> Bool #

(/=) :: (k -> v) -> (k -> v) -> Bool #

(Bounded k, Enum k, Ord k, Ord v) => Ord (k -> v) Source # 
Instance details

Methods

compare :: (k -> v) -> (k -> v) -> Ordering #

(<) :: (k -> v) -> (k -> v) -> Bool #

(<=) :: (k -> v) -> (k -> v) -> Bool #

(>) :: (k -> v) -> (k -> v) -> Bool #

(>=) :: (k -> v) -> (k -> v) -> Bool #

max :: (k -> v) -> (k -> v) -> k -> v #

min :: (k -> v) -> (k -> v) -> k -> v #