puzzle-draw-0.3.0.0: Creating graphics for pencil puzzles.

Safe HaskellSafe
LanguageHaskell98

Data.Elements

Description

Types for a variety of puzzle elements.

Synopsis

Documentation

type Clue a = Maybe a Source #

data MasyuPearl Source #

Constructors

MWhite 
MBlack 
Instances
Eq MasyuPearl Source # 
Instance details

Defined in Data.Elements

Show MasyuPearl Source # 
Instance details

Defined in Data.Elements

FromChar MasyuPearl Source # 
Instance details

Defined in Parse.Util

data CompassC Source #

A Compass clue, specifiying optional numbers in the four cardinal directions.

Constructors

CC (Maybe Int) (Maybe Int) (Maybe Int) (Maybe Int) 
Instances
Show CompassC Source # 
Instance details

Defined in Data.Elements

data SlovakClue Source #

Constructors

SlovakClue !Int !Int 

data Tightfit a Source #

A cell that is optionally bisected by a diagonal (up-right or down-right).

Constructors

Single a 
UR a a 
DR a a 
Instances
Show a => Show (Tightfit a) Source # 
Instance details

Defined in Data.Elements

Methods

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

show :: Tightfit a -> String #

showList :: [Tightfit a] -> ShowS #

FromChar a => FromString (Tightfit a) Source # 
Instance details

Defined in Parse.Util

data MarkedLine a Source #

A marked line in a grid, given by start and end points.

Constructors

MarkedLine a a 

data MarkedWord Source #

A marked word in a letter grid, by its start and end coordinates.

Constructors

MW 

Fields

type Loop a = [Edge a] Source #

A loop of edges.

type VertexLoop = [N] Source #

A loop consisting of straight segments of arbitrary angles between vertices.

type Thermometer = [C] Source #

A thermometer, as a list of coordinates from bulb to end. There should be at least two entries, entries should be distinct, and successive entries should be neighbours (diagonal neighbours are fine).

data SlalomDiag Source #

A forward or backward diagonal as occurring in the solution of a slalom puzzle.

Instances
Show SlalomDiag Source # 
Instance details

Defined in Data.Elements

FromChar SlalomDiag Source # 
Instance details

Defined in Parse.Util

data Shade Source #

Shadow along from the western and southern side, as used for afternoon skyscrapers.

Constructors

Shade Bool Bool 
Instances
Show Shade Source # 
Instance details

Defined in Data.Elements

Methods

showsPrec :: Int -> Shade -> ShowS #

show :: Shade -> String #

showList :: [Shade] -> ShowS #

data KropkiDot Source #

Constructors

KNone 
KBlack 
KWhite 
Instances
Eq KropkiDot Source # 
Instance details

Defined in Data.Elements

Ord KropkiDot Source # 
Instance details

Defined in Data.Elements

Show KropkiDot Source # 
Instance details

Defined in Data.Elements

FromChar KropkiDot Source # 
Instance details

Defined in Parse.Util

newtype TapaClue Source #

Constructors

TapaClue [Int] 
Instances
Show TapaClue Source # 
Instance details

Defined in Data.Elements

newtype PrimeDiag Source #

Diagonal marking for Prime Place: forward diag?, backward diag?

Constructors

PrimeDiag (Bool, Bool) 
Instances
FromChar PrimeDiag Source # 
Instance details

Defined in Parse.Util

data Black Source #

Constructors

Black 
Instances
Eq Black Source # 
Instance details

Defined in Data.Elements

Methods

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

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

FromChar Black Source # 
Instance details

Defined in Parse.Util

data Fish Source #

Constructors

Fish 
Instances
Eq Fish Source # 
Instance details

Defined in Data.Elements

Methods

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

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

FromChar Fish Source # 
Instance details

Defined in Parse.Util

data Star Source #

Constructors

Star 
Instances
Eq Star Source # 
Instance details

Defined in Data.Elements

Methods

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

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

FromChar Star Source # 
Instance details

Defined in Parse.Util

data Crossing Source #

Constructors

Crossing 
Instances
Eq Crossing Source # 
Instance details

Defined in Data.Elements

FromChar Crossing Source # 
Instance details

Defined in Parse.Util

data DigitRange Source #

Constructors

DigitRange !Int !Int 
Instances
Eq DigitRange Source # 
Instance details

Defined in Data.Elements

Show DigitRange Source # 
Instance details

Defined in Data.Elements

FromString DigitRange Source # 
Instance details

Defined in Parse.Util

data MEnd Source #

Constructors

MEnd 
Instances
FromChar MEnd Source # 
Instance details

Defined in Parse.Util

data PlainNode Source #

Constructors

PlainNode 
Instances
FromChar PlainNode Source # 
Instance details

Defined in Parse.Util

type Myopia = [Dir'] Source #

data Relation Source #

Instances
Eq Relation Source # 
Instance details

Defined in Data.Elements

Show Relation Source # 
Instance details

Defined in Data.Elements

FromChar Relation Source # 
Instance details

Defined in Parse.Util

data GalaxyCentre Source #

Constructors

GalaxyCentre 
Instances
FromChar GalaxyCentre Source # 
Instance details

Defined in Parse.Util

data PlacedTent Source #

Constructors

Tent Dir' 
Instances
FromChar PlacedTent Source # 
Instance details

Defined in Parse.Util

data Tree Source #

Constructors

Tree 
Instances
FromChar Tree Source # 
Instance details

Defined in Parse.Util

data Pentomino Source #

Constructors

Pentomino Char 
Instances
Eq Pentomino Source # 
Instance details

Defined in Data.Elements

Show Pentomino Source # 
Instance details

Defined in Data.Elements

FromChar Pentomino Source # 
Instance details

Defined in Parse.Util