Safe Haskell | None |
---|---|
Language | Haskell2010 |
Game.Goatee.Lib.Property
Description
Structures and functions for working with SGF node properties.
Synopsis
- data Property
- = B (Maybe Coord)
- | KO
- | MN Integer
- | W (Maybe Coord)
- | AB CoordList
- | AE CoordList
- | AW CoordList
- | PL Color
- | C Text
- | DM DoubleValue
- | GB DoubleValue
- | GW DoubleValue
- | HO DoubleValue
- | N SimpleText
- | UC DoubleValue
- | V RealValue
- | BM DoubleValue
- | DO
- | IT
- | TE DoubleValue
- | AR ArrowList
- | CR CoordList
- | DD CoordList
- | LB LabelList
- | LN LineList
- | MA CoordList
- | SL CoordList
- | SQ CoordList
- | TR CoordList
- | AP SimpleText SimpleText
- | CA SimpleText
- | FF Int
- | GM Int
- | ST VariationMode
- | SZ Int Int
- | AN SimpleText
- | BR SimpleText
- | BT SimpleText
- | CP SimpleText
- | DT SimpleText
- | EV SimpleText
- | GC Text
- | GN SimpleText
- | ON SimpleText
- | OT SimpleText
- | PB SimpleText
- | PC SimpleText
- | PW SimpleText
- | RE GameResult
- | RO SimpleText
- | RU Ruleset
- | SO SimpleText
- | TM RealValue
- | US SimpleText
- | WR SimpleText
- | WT SimpleText
- | BL RealValue
- | OB Int
- | OW Int
- | WL RealValue
- | VW CoordList
- | HA Int
- | KM RealValue
- | TB CoordList
- | TW CoordList
- | UnknownProperty String UnknownPropertyValue
- data PropertyType
- class Descriptor a where
- propertyName :: a -> String
- propertyType :: a -> PropertyType
- propertyInherited :: a -> Bool
- propertyPredicate :: a -> Property -> Bool
- propertyValueParser :: a -> Parser Property
- propertyValueRenderer :: a -> Property -> Render ()
- propertyValueRendererPretty :: a -> Property -> Render ()
- class (Descriptor a, Eq v) => ValuedDescriptor v a | a -> v where
- propertyValue :: a -> Property -> v
- propertyBuilder :: a -> v -> Property
- data AnyDescriptor = forall a.Descriptor a => AnyDescriptor a
- data AnyValuedDescriptor v = forall a.ValuedDescriptor v a => AnyValuedDescriptor a
- type AnyCoordListDescriptor = AnyValuedDescriptor CoordList
- data PropertyInfo
- data ValuedPropertyInfo v = ValuedPropertyInfo String PropertyType Bool (Property -> Bool) (PropertyValueType v) (Property -> v) (v -> Property)
- defProperty :: String -> Name -> Bool -> DecsQ
- defValuedProperty :: String -> Name -> Bool -> Name -> DecsQ
- propertyB :: ValuedPropertyInfo (Maybe Coord)
- propertyKO :: PropertyInfo
- propertyMN :: ValuedPropertyInfo Integer
- propertyW :: ValuedPropertyInfo (Maybe Coord)
- propertyAB :: ValuedPropertyInfo CoordList
- propertyAE :: ValuedPropertyInfo CoordList
- propertyAW :: ValuedPropertyInfo CoordList
- propertyPL :: ValuedPropertyInfo Color
- propertyC :: ValuedPropertyInfo Text
- propertyDM :: ValuedPropertyInfo DoubleValue
- propertyGB :: ValuedPropertyInfo DoubleValue
- propertyGW :: ValuedPropertyInfo DoubleValue
- propertyHO :: ValuedPropertyInfo DoubleValue
- propertyN :: ValuedPropertyInfo SimpleText
- propertyUC :: ValuedPropertyInfo DoubleValue
- propertyV :: ValuedPropertyInfo RealValue
- propertyBM :: ValuedPropertyInfo DoubleValue
- propertyDO :: PropertyInfo
- propertyIT :: PropertyInfo
- propertyTE :: ValuedPropertyInfo DoubleValue
- propertyAR :: ValuedPropertyInfo ArrowList
- propertyCR :: ValuedPropertyInfo CoordList
- propertyDD :: ValuedPropertyInfo CoordList
- propertyLB :: ValuedPropertyInfo LabelList
- propertyLN :: ValuedPropertyInfo LineList
- propertyMA :: ValuedPropertyInfo CoordList
- propertySL :: ValuedPropertyInfo CoordList
- propertySQ :: ValuedPropertyInfo CoordList
- propertyTR :: ValuedPropertyInfo CoordList
- propertyAP :: ValuedPropertyInfo (SimpleText, SimpleText)
- propertyCA :: ValuedPropertyInfo SimpleText
- propertyFF :: ValuedPropertyInfo Int
- propertyGM :: ValuedPropertyInfo Int
- propertyST :: ValuedPropertyInfo VariationMode
- propertySZ :: ValuedPropertyInfo (Int, Int)
- propertyAN :: ValuedPropertyInfo SimpleText
- propertyBR :: ValuedPropertyInfo SimpleText
- propertyBT :: ValuedPropertyInfo SimpleText
- propertyCP :: ValuedPropertyInfo SimpleText
- propertyDT :: ValuedPropertyInfo SimpleText
- propertyEV :: ValuedPropertyInfo SimpleText
- propertyGC :: ValuedPropertyInfo Text
- propertyGN :: ValuedPropertyInfo SimpleText
- propertyON :: ValuedPropertyInfo SimpleText
- propertyOT :: ValuedPropertyInfo SimpleText
- propertyPB :: ValuedPropertyInfo SimpleText
- propertyPC :: ValuedPropertyInfo SimpleText
- propertyPW :: ValuedPropertyInfo SimpleText
- propertyRE :: ValuedPropertyInfo GameResult
- propertyRO :: ValuedPropertyInfo SimpleText
- propertyRU :: ValuedPropertyInfo Ruleset
- propertySO :: ValuedPropertyInfo SimpleText
- propertyTM :: ValuedPropertyInfo RealValue
- propertyUS :: ValuedPropertyInfo SimpleText
- propertyWR :: ValuedPropertyInfo SimpleText
- propertyWT :: ValuedPropertyInfo SimpleText
- propertyBL :: ValuedPropertyInfo RealValue
- propertyOB :: ValuedPropertyInfo Int
- propertyOW :: ValuedPropertyInfo Int
- propertyWL :: ValuedPropertyInfo RealValue
- propertyVW :: ValuedPropertyInfo CoordList
- propertyHA :: ValuedPropertyInfo Int
- propertyKM :: ValuedPropertyInfo RealValue
- propertyTB :: ValuedPropertyInfo CoordList
- propertyTW :: ValuedPropertyInfo CoordList
- allKnownDescriptors :: [AnyDescriptor]
- propertyUnknown :: String -> ValuedPropertyInfo UnknownPropertyValue
- propertyInfo :: Property -> AnyDescriptor
- descriptorForName :: String -> AnyDescriptor
- descriptorForName' :: String -> Maybe AnyDescriptor
- stoneAssignmentProperties :: [AnyCoordListDescriptor]
- stoneAssignmentPropertyToStone :: AnyCoordListDescriptor -> Maybe Color
- stoneToStoneAssignmentProperty :: Maybe Color -> AnyCoordListDescriptor
- markProperty :: Mark -> ValuedPropertyInfo CoordList
Properties
An SGF property that gives a node meaning. A property is known if its
meaning is defined by the SGF specification, and unknown otherwise. Known
properties each have their own data constructors. Unknown properties are
represented by the UnknownProperty
data constructor.
Constructors
B (Maybe Coord) | Black move (nothing iff pass). |
KO | Execute move unconditionally (even if illegal). |
MN Integer | Assign move number. |
W (Maybe Coord) | White move (nothing iff pass). |
AB CoordList | Assign black stones. |
AE CoordList | Assign empty stones. |
AW CoordList | Assign white stones. |
PL Color | Player to play. |
C Text | Comment. |
DM DoubleValue | Even position. |
GB DoubleValue | Good for black. |
GW DoubleValue | Good for white. |
HO DoubleValue | Hotspot. |
N SimpleText | Node name. |
UC DoubleValue | Unclear position. |
V RealValue | Node value. |
BM DoubleValue | Bad move. |
DO | Doubtful move. |
IT | Interesting move. |
TE DoubleValue | Tesuji. |
AR ArrowList | Arrows. |
CR CoordList | Mark points with circles. |
DD CoordList | Dim points. |
LB LabelList | Label points with text. |
LN LineList | Lines. |
MA CoordList | Mark points with |
SL CoordList | Mark points as selected. |
SQ CoordList | Mark points with squares. |
TR CoordList | Mark points with trianges. |
AP SimpleText SimpleText | Application info. |
CA SimpleText | Charset for SimpleText and Text. |
FF Int | File format version. |
GM Int | Game (must be 1 = Go). |
ST VariationMode | Variation display format. |
SZ Int Int | Board size, columns then rows. |
AN SimpleText | Name of annotator. |
BR SimpleText | Rank of black player. |
BT SimpleText | Name of black team. |
CP SimpleText | Copyright info. |
DT SimpleText | Dates played. |
EV SimpleText | Event name. |
GC Text | Game comment, or background, or summary. |
GN SimpleText | Game name. |
ON SimpleText | Information about the opening. |
OT SimpleText | The method used for overtime. |
PB SimpleText | Name of black player. |
PC SimpleText | Where the game was played. |
PW SimpleText | Name of white player. |
RE GameResult | Result of the game. |
RO SimpleText | Round info. |
RU Ruleset | Ruleset used. |
SO SimpleText | Source of the game. |
TM RealValue | Time limit, in seconds. |
US SimpleText | Name of user or program who entered the game. |
WR SimpleText | Rank of white player. |
WT SimpleText | Name of white team. |
BL RealValue | Black time left. |
OB Int | Black moves left in byo-yomi period. |
OW Int | White moves left in byo-yomi period. |
WL RealValue | White time left. |
VW CoordList | Set viewing region. |
HA Int | Handicap stones (>=2). |
KM RealValue | Komi. |
TB CoordList | Black territory. |
TW CoordList | White territory. |
UnknownProperty String UnknownPropertyValue |
Instances
Eq Property Source # | |
Show Property Source # | |
Descriptor Property Source # | |
Defined in Game.Goatee.Lib.Property.Info Methods propertyName :: Property -> String Source # propertyType :: Property -> PropertyType Source # propertyInherited :: Property -> Bool Source # propertyPredicate :: Property -> Property -> Bool Source # propertyValueParser :: Property -> Parser Property Source # propertyValueRenderer :: Property -> Property -> Render () Source # propertyValueRendererPretty :: Property -> Property -> Render () Source # |
Property metadata
data PropertyType Source #
The property types that SGF uses to group properties.
Constructors
MoveProperty | Cannot mix with setup nodes. |
SetupProperty | Cannot mix with move nodes. |
RootProperty | May only appear in root nodes. |
GameInfoProperty | At most one on any path. |
GeneralProperty | May appear anywhere in the game tree. |
Instances
Eq PropertyType Source # | |
Defined in Game.Goatee.Lib.Property.Base | |
Show PropertyType Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods showsPrec :: Int -> PropertyType -> ShowS # show :: PropertyType -> String # showList :: [PropertyType] -> ShowS # |
class Descriptor a where Source #
A class for types that contain metadata about a Property
. The main
instance of this class is Property
itself; Property
s can be treated as
though they have metadata directly. When referring to a property in general
rather than a specific instance, use the values of PropertyInfo
and
ValuedPropertyInfo
.
See also ValuedDescriptor
.
Methods
propertyName :: a -> String Source #
Returns the name of the property, as used in SGF files.
propertyType :: a -> PropertyType Source #
Returns the type of the property, as specified by the SGF spec.
propertyInherited :: a -> Bool Source #
Returns whether the value of the given property is inherited from the lowest ancestor specifying the property, when the property is not set on a node itself.
propertyPredicate :: a -> Property -> Bool Source #
Returns whether the given property has the type of a descriptor.
propertyValueParser :: a -> Parser Property Source #
A parser of property values in SGF format (e.g. "[ab]"
for a property
that takes a point).
propertyValueRenderer :: a -> Property -> Render () Source #
A renderer property values to SGF format (e.g. B (Just (1,2))
renders
to "[ab]"
).
propertyValueRendererPretty :: a -> Property -> Render () Source #
A renderer for displaying property values in a UI. Displays the value in a human-readable format.
Instances
class (Descriptor a, Eq v) => ValuedDescriptor v a | a -> v where Source #
A class for Descriptor
s of properties that also contain values.
Methods
propertyValue :: a -> Property -> v Source #
Extracts the value from a property of the given type. Behaviour is undefined if the property is not of the given type.
propertyBuilder :: a -> v -> Property Source #
Builds a property from a given value.
Instances
Eq v => ValuedDescriptor v (ValuedPropertyInfo v) Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyValue :: ValuedPropertyInfo v -> Property -> v Source # propertyBuilder :: ValuedPropertyInfo v -> v -> Property Source # | |
Eq v => ValuedDescriptor v (AnyValuedDescriptor v) Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyValue :: AnyValuedDescriptor v -> Property -> v Source # propertyBuilder :: AnyValuedDescriptor v -> v -> Property Source # |
data AnyDescriptor Source #
An existential type for any property descriptor. AnyDescriptor
has a
Descriptor
instance, so there is no need to extract the value with a
pattern match before using Descriptor
methods.
Constructors
forall a.Descriptor a => AnyDescriptor a |
Instances
Descriptor AnyDescriptor Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyName :: AnyDescriptor -> String Source # propertyType :: AnyDescriptor -> PropertyType Source # propertyInherited :: AnyDescriptor -> Bool Source # propertyPredicate :: AnyDescriptor -> Property -> Bool Source # propertyValueParser :: AnyDescriptor -> Parser Property Source # propertyValueRenderer :: AnyDescriptor -> Property -> Render () Source # propertyValueRendererPretty :: AnyDescriptor -> Property -> Render () Source # |
data AnyValuedDescriptor v Source #
An existential type for any descriptor of a property that holds a value of
a specific type. Has instances for Descriptor
and ValuedDescriptor
,
similar to AnyDescriptor
.
Constructors
forall a.ValuedDescriptor v a => AnyValuedDescriptor a |
Instances
Eq v => ValuedDescriptor v (AnyValuedDescriptor v) Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyValue :: AnyValuedDescriptor v -> Property -> v Source # propertyBuilder :: AnyValuedDescriptor v -> v -> Property Source # | |
Descriptor (AnyValuedDescriptor v) Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyName :: AnyValuedDescriptor v -> String Source # propertyType :: AnyValuedDescriptor v -> PropertyType Source # propertyInherited :: AnyValuedDescriptor v -> Bool Source # propertyPredicate :: AnyValuedDescriptor v -> Property -> Bool Source # propertyValueParser :: AnyValuedDescriptor v -> Parser Property Source # propertyValueRenderer :: AnyValuedDescriptor v -> Property -> Render () Source # propertyValueRendererPretty :: AnyValuedDescriptor v -> Property -> Render () Source # |
data PropertyInfo Source #
Metadata for a property that does not contain a value. Corresponds to a
nullary data constructor of Property
.
Instances
Descriptor PropertyInfo Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyName :: PropertyInfo -> String Source # propertyType :: PropertyInfo -> PropertyType Source # propertyInherited :: PropertyInfo -> Bool Source # propertyPredicate :: PropertyInfo -> Property -> Bool Source # propertyValueParser :: PropertyInfo -> Parser Property Source # propertyValueRenderer :: PropertyInfo -> Property -> Render () Source # propertyValueRendererPretty :: PropertyInfo -> Property -> Render () Source # |
data ValuedPropertyInfo v Source #
Metadata for a property that contains a value. Corresponds to a
non-nullary data constructor of Property
.
Constructors
ValuedPropertyInfo String PropertyType Bool (Property -> Bool) (PropertyValueType v) (Property -> v) (v -> Property) |
Instances
Eq v => ValuedDescriptor v (ValuedPropertyInfo v) Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyValue :: ValuedPropertyInfo v -> Property -> v Source # propertyBuilder :: ValuedPropertyInfo v -> v -> Property Source # | |
Descriptor (ValuedPropertyInfo v) Source # | |
Defined in Game.Goatee.Lib.Property.Base Methods propertyName :: ValuedPropertyInfo v -> String Source # propertyType :: ValuedPropertyInfo v -> PropertyType Source # propertyInherited :: ValuedPropertyInfo v -> Bool Source # propertyPredicate :: ValuedPropertyInfo v -> Property -> Bool Source # propertyValueParser :: ValuedPropertyInfo v -> Parser Property Source # propertyValueRenderer :: ValuedPropertyInfo v -> Property -> Render () Source # propertyValueRendererPretty :: ValuedPropertyInfo v -> Property -> Render () Source # |
(Internal) Property metadata declaration
Arguments
:: String | The SGF textual name of the property. |
-> Name | The name of the |
-> Bool | Whether the property is inherited. |
-> DecsQ |
Internal to this module, do not use outside. Template Haskell function to declare a property that does not contain a value.
$(defProperty "KO" 'MoveProperty False)
This example declares a propertyKO ::
that is a
PropertyInfo
MoveProperty
and is not inherited.
defValuedProperty :: String -> Name -> Bool -> Name -> DecsQ Source #
Internal to this module, do not use outside. Template Haskell function to declare a property that contains a value.
$(defValuedProperty "B" 'MoveProperty False 'maybeCoordPrinter)
This example declares a propertyB ::
that is a ValuedPropertyInfo
(Maybe Coord
)MoveProperty
and is not inherited. The value type is
automatically inferred.
Known property metadata
propertySZ :: ValuedPropertyInfo (Int, Int) Source #
Property metadata utilities
allKnownDescriptors :: [AnyDescriptor] Source #
A list of descriptors for all known Property
s.
propertyUnknown :: String -> ValuedPropertyInfo UnknownPropertyValue Source #
Builds a ValuedPropertyInfo
for an unknown property with the given name.
Does not check that the name is actually unknown.
propertyInfo :: Property -> AnyDescriptor Source #
Returns a descriptor for any Property
, known or unknown. Because a
Property
has a Descriptor
instance, this function is not normally
necessary for use outside of this module, but it can be used to throw away a
value associated with a Property
and retain only the metadata.
descriptorForName :: String -> AnyDescriptor Source #
Returns a descriptor for the given property name. The name does not have
to be for a known property; an unknown property will use propertyUnknown
.
descriptorForName' :: String -> Maybe AnyDescriptor Source #
Returns a descriptor for a known property with the given name, or Nothing
if the name does not belong to a known property.
stoneAssignmentProperties :: [AnyCoordListDescriptor] Source #
Descriptors for setup properties that assign stones to the board. For use
with stoneAssignmentPropertyToStone
and stoneToStoneAssignmentProperty
.
stoneAssignmentPropertyToStone :: AnyCoordListDescriptor -> Maybe Color Source #
Converts a descriptor in stoneAssignmentProperties
to the type of stone
it assigns.
stoneToStoneAssignmentProperty :: Maybe Color -> AnyCoordListDescriptor Source #
Converts a type of stone assignment to a descriptor in
stoneAssignmentProperties
.
markProperty :: Mark -> ValuedPropertyInfo CoordList Source #
Returns the descriptor for a mark.