goatee-0.3.1.3: A monadic take on a 2,500-year-old board game - library.

Safe HaskellSafe
LanguageHaskell98

Game.Goatee.Lib.Types

Contents

Description

Constants and data types for property values used in SGF game trees.

Synopsis

Constants

supportedFormatVersions :: [Int] Source #

The FF versions supported by Goatee. Currently only 4.

defaultFormatVersion :: Int Source #

The default SGF version to use when FF[] is not specified in a root node.

This value is actually INCORRECT: SGF defines it to be 1, but because we don't support version 1 yet, for the sake of ignoring this issue (for now!) in tests, we fix the default to be 4.

supportedGameTypes :: [Int] Source #

SGF supports multiple game types. This list contains the game types that Goatee supports, which is only Go (1).

boardSizeDefault :: Int Source #

The default size of the board. The FF[4] SGF spec says that the default Go board is 19x19 square.

boardSizeMin :: Int Source #

The minimum board size allowed by FF[4], 1.

boardSizeMax :: Int Source #

The maximum board size allowed by FF[4], 52.

Board coordinates

type Coord = (Int, Int) Source #

A coordinate on a Go board. (0, 0) refers to the upper-left corner of the board. The first component is the horizontal position; the second component is the vertical position.

data CoordList Source #

A structure for compact representation of a list of coordinates. Contains a list of individual points, as well as a list of rectangles of points denoted by an ordered pair of the upper-left point and the lower-right point. The union of the single points and points contained within rectangles make up all of the points a CoordList represents. There is no rule saying that adjacent points have to be grouped into rectangles; it's perfectly valid (although possibly inefficient) to never use rectangles.

For any CoordList, all of the following hold:

  1. Any point may be specified at most once, either in the singles list or in a single rectangle.
  2. For a rectangle ((x0,y0), (x1,y1)), x0 <= x1 and y0 <= y1 and (x0,y0) /= (x1,y1) (otherwise the point belongs in the singles list).
Instances
Eq CoordList Source #

Equality is based on unordered, set equality of the underlying points.

Instance details

Defined in Game.Goatee.Lib.Types

Show CoordList Source # 
Instance details

Defined in Game.Goatee.Lib.Types

coordListSingles :: CoordList -> [Coord] Source #

Returns the single points in a CoordList.

coordListRects :: CoordList -> [(Coord, Coord)] Source #

Returns the rectangles in a CoordList.

coord1 :: Coord -> CoordList Source #

Constructs a CoordList containing a single point.

coords :: [Coord] -> CoordList Source #

Constructs a CoordList containing the given single points. For rectangle detection, use buildCoordList.

coords' :: [Coord] -> [(Coord, Coord)] -> CoordList Source #

Constructs a CoordList containing the given single points and rectangles.

emptyCoordList :: CoordList Source #

A CoordList that contains no points.

expandCoordList :: CoordList -> [Coord] Source #

Converts a compact CoordList to a list of coordinates.

buildCoordList :: [Coord] -> CoordList Source #

Constructs a CoordList from a list of Coords, doing some not-completely-stupid rectangle detection. The order of data in the result is unspecified.

Star points and handicap stones

starLines :: Int -> Int -> Maybe [Int] Source #

starLines width height returns Just a list of row/column indices that have star points on a board of the given size, or Nothing if the board size does not have star points defined.

isStarPoint :: Int -> Int -> Int -> Int -> Bool Source #

isStarPoint width height x y determines whether (x, y) is a known star point on a board of the given width and height.

handicapStones :: Int -> Int -> Int -> Maybe [Coord] Source #

handicapStones width height handicap returns a list of points where handicap stones should be placed for the given handicap, if handicap points are defined for the given board size, otherwise Nothing.

Property values

Text values

class Stringlike a where Source #

A class for SGF data types that are coercable to and from strings.

The construction of an SGF value with stringToSgf may process the input, such that the resulting stringlike value does not represent the same string as the input. In other words, the following does *not* necessarily hold:

sgfToString . stringToSgf = id   (does not necessarily hold!)

The following does hold, however, for a single stringlike type:

stringToSgf . sgfToString = id

The String instance is defined with sgfToString = stringToSgf = id. For other types, the string returned by sgfToString is in a raw, user-editable format: characters that need to be escaped in serialized SGF aren't escaped, but the returned value is otherwise similar to SGF format.

Minimal complete definition

sgfToString, stringToSgf

Methods

sgfToString :: a -> String Source #

Extracts the string value from an SGF value.

stringToSgf :: String -> a Source #

Creates an SGF value from a string value.

convertStringlike :: (Stringlike a, Stringlike b) => a -> b Source #

Converts between Stringlike types via a string.

convertStringlike = stringToSgf . sgfToString

data Text Source #

An SGF text value.

Instances
Eq Text Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

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

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

Show Text Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

showsPrec :: Int -> Text -> ShowS #

show :: Text -> String #

showList :: [Text] -> ShowS #

Stringlike Text Source # 
Instance details

Defined in Game.Goatee.Lib.Types

fromText :: Text -> String Source #

Converts an SGF Text to a string.

toText :: String -> Text Source #

Converts a string to an SGF Text.

data SimpleText Source #

An SGF SimpleText value.

fromSimpleText :: SimpleText -> String Source #

Converts an SGF SimpleText to a string.

toSimpleText :: String -> SimpleText Source #

Converts a string to an SGF SimpleText, replacing all whitespaces (including newlines) with spaces.

Other values

fromUnknownPropertyValue :: UnknownPropertyValue -> String Source #

Returns the string contained within the UnknownProperty this value is from.

toUnknownPropertyValue :: String -> UnknownPropertyValue Source #

Constructs a value for a UnknownProperty.

type RealValue = Bigfloat Source #

An SGF real value is a decimal number of unspecified precision.

data Color Source #

Stone color: black or white.

Constructors

Black 
White 
Instances
Bounded Color Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Enum Color Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Eq Color Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

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

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

Ord Color Source # 
Instance details

Defined in Game.Goatee.Lib.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 #

Show Color Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

cnot :: Color -> Color Source #

Returns the logical negation of a stone color, yang for yin and yin for yang.

data VariationMode Source #

SGF flags that control how move variations are to be presented while displaying the game.

Constructors

VariationMode 

Fields

data VariationModeSource Source #

An enumeration that describes which variations are shown.

Constructors

ShowChildVariations

Show children of the current move.

ShowCurrentVariations

Show alternatives to the current move.

Instances
Bounded VariationModeSource Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Enum VariationModeSource Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Eq VariationModeSource Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Ord VariationModeSource Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Show VariationModeSource Source # 
Instance details

Defined in Game.Goatee.Lib.Types

defaultVariationMode :: VariationMode Source #

The default variation mode as defined by the SGF spec is VariationMode ShowChildVariations True.

toVariationMode :: Int -> Maybe VariationMode Source #

Parses a numeric variation mode, returning nothing if the number is invalid.

fromVariationMode :: VariationMode -> Int Source #

Returns the integer value for a variation mode.

type ArrowList = [(Coord, Coord)] Source #

A list of arrows, each specified as (startCoord, endCoord).

type LineList = [Line] Source #

A list of lines, each specified as (startCoord, endCoord).

data Line Source #

An undirected line between two coordinates.

Constructors

Line Coord Coord 
Instances
Eq Line Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

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

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

Show Line Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

lineToPair :: Line -> (Coord, Coord) Source #

Converts a Line to a pair of Coords representing the line's endpoints.

type LabelList = [(Coord, SimpleText)] Source #

A list of labels, each specified with a string and a coordinate about which to center the string.

data Mark Source #

The markings that SGF supports annotating coordinates with.

Instances
Bounded Mark Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Enum Mark Source # 
Instance details

Defined in Game.Goatee.Lib.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] #

Eq Mark Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

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

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

Ord Mark Source # 
Instance details

Defined in Game.Goatee.Lib.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 #

Show Mark Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

showsPrec :: Int -> Mark -> ShowS #

show :: Mark -> String #

showList :: [Mark] -> ShowS #

data Ruleset Source #

A ruleset used for a Go game. Can be one of the rulesets defined by the SGF specification, or a custom string.

Instances
Eq Ruleset Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Methods

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

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

Show Ruleset Source # 
Instance details

Defined in Game.Goatee.Lib.Types

Stringlike Ruleset Source # 
Instance details

Defined in Game.Goatee.Lib.Types

data RulesetType Source #

The rulesets defined by the SGF specification, for use with Ruleset.

fromRuleset :: Ruleset -> String Source #

Returns the string representation for a ruleset.

toRuleset :: String -> Ruleset Source #

Parses a string representation of a ruleset.