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

Safe HaskellSafe
LanguageHaskell98

Data.GridShape

Description

Grid shapes.

Synopsis

Documentation

type Coord = (Int, Int) Source #

type Size = (Int, Int) Source #

data Square Source #

A standard square grid, with cells and vertices indexed by pairs of integers in mathematical coordinates. The bottom-left corner is vertex (0, 0), the bottom-left cell is cell (0, 0).

Constructors

Square 
Instances
Eq Square Source # 
Instance details

Defined in Data.GridShape

Methods

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

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

Show Square Source # 
Instance details

Defined in Data.GridShape

data Dir Source #

Edge direction in a square grid, vertical or horizontal.

Constructors

Vert 
Horiz 
Instances
Eq Dir Source # 
Instance details

Defined in Data.GridShape

Methods

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

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

Ord Dir Source # 
Instance details

Defined in Data.GridShape

Methods

compare :: Dir -> Dir -> Ordering #

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

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

(>) :: Dir -> Dir -> Bool #

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

max :: Dir -> Dir -> Dir #

min :: Dir -> Dir -> Dir #

Show Dir Source # 
Instance details

Defined in Data.GridShape

Methods

showsPrec :: Int -> Dir -> ShowS #

show :: Dir -> String #

showList :: [Dir] -> ShowS #

data Edge a Source #

An edge in a square grid, going up or right from the given cell centre.

Constructors

E a Dir 
Instances
Eq a => Eq (Edge a) Source # 
Instance details

Defined in Data.GridShape

Methods

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

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

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

Defined in Data.GridShape

Methods

compare :: Edge a -> Edge a -> Ordering #

(<) :: Edge a -> Edge a -> Bool #

(<=) :: Edge a -> Edge a -> Bool #

(>) :: Edge a -> Edge a -> Bool #

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

max :: Edge a -> Edge a -> Edge a #

min :: Edge a -> Edge a -> Edge a #

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

Defined in Data.GridShape

Methods

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

show :: Edge a -> String #

showList :: [Edge a] -> ShowS #

data Dir' Source #

Oriented edge direction in a square grid.

Constructors

U 
D 
L 
R 
Instances
Eq Dir' Source # 
Instance details

Defined in Data.GridShape

Methods

(==) :: Dir' -> Dir' -> Bool #

(/=) :: Dir' -> Dir' -> Bool #

Ord Dir' Source # 
Instance details

Defined in Data.GridShape

Methods

compare :: Dir' -> Dir' -> Ordering #

(<) :: Dir' -> Dir' -> Bool #

(<=) :: Dir' -> Dir' -> Bool #

(>) :: Dir' -> Dir' -> Bool #

(>=) :: Dir' -> Dir' -> Bool #

max :: Dir' -> Dir' -> Dir' #

min :: Dir' -> Dir' -> Dir' #

Show Dir' Source # 
Instance details

Defined in Data.GridShape

Methods

showsPrec :: Int -> Dir' -> ShowS #

show :: Dir' -> String #

showList :: [Dir'] -> ShowS #

FromChar Dir' Source # 
Instance details

Defined in Parse.Util

data Edge' a Source #

An oriented edge in a square grid.

Constructors

E' a Dir' 
Instances
Eq a => Eq (Edge' a) Source # 
Instance details

Defined in Data.GridShape

Methods

(==) :: Edge' a -> Edge' a -> Bool #

(/=) :: Edge' a -> Edge' a -> Bool #

Ord a => Ord (Edge' a) Source # 
Instance details

Defined in Data.GridShape

Methods

compare :: Edge' a -> Edge' a -> Ordering #

(<) :: Edge' a -> Edge' a -> Bool #

(<=) :: Edge' a -> Edge' a -> Bool #

(>) :: Edge' a -> Edge' a -> Bool #

(>=) :: Edge' a -> Edge' a -> Bool #

max :: Edge' a -> Edge' a -> Edge' a #

min :: Edge' a -> Edge' a -> Edge' a #

Show a => Show (Edge' a) Source # 
Instance details

Defined in Data.GridShape

Methods

showsPrec :: Int -> Edge' a -> ShowS #

show :: Edge' a -> String #

showList :: [Edge' a] -> ShowS #

class Dual2D a where Source #

Minimal complete definition

dualE'

Associated Types

type Dual a :: * Source #

Methods

dualE' :: Edge' a -> Edge' (Dual a) Source #

Instances
Dual2D N Source # 
Instance details

Defined in Data.GridShape

Associated Types

type Dual N :: * Source #

Methods

dualE' :: Edge' N -> Edge' (Dual N) Source #

Dual2D C Source # 
Instance details

Defined in Data.GridShape

Associated Types

type Dual C :: * Source #

Methods

dualE' :: Edge' C -> Edge' (Dual C) Source #

type Key k = (AffineSpace k, Diff k ~ (Int, Int), Ord k, FromCoord k) Source #

type Dual' k = (Key k, Dual2D k, Key (Dual k), Dual2D (Dual k), Dual (Dual k) ~ k) Source #

data C Source #

Constructors

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

Defined in Data.GridShape

Methods

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

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

Ord C Source # 
Instance details

Defined in Data.GridShape

Methods

compare :: C -> C -> Ordering #

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

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

(>) :: C -> C -> Bool #

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

max :: C -> C -> C #

min :: C -> C -> C #

Show C Source # 
Instance details

Defined in Data.GridShape

Methods

showsPrec :: Int -> C -> ShowS #

show :: C -> String #

showList :: [C] -> ShowS #

AffineSpace C Source # 
Instance details

Defined in Data.GridShape

Associated Types

type Diff C :: * #

Methods

(.-.) :: C -> C -> Diff C #

(.+^) :: C -> Diff C -> C #

Dual2D C Source # 
Instance details

Defined in Data.GridShape

Associated Types

type Dual C :: * Source #

Methods

dualE' :: Edge' C -> Edge' (Dual C) Source #

ToCoord C Source # 
Instance details

Defined in Data.GridShape

Methods

toCoord :: C -> Coord Source #

FromCoord C Source # 
Instance details

Defined in Data.GridShape

Methods

fromCoord :: Coord -> C Source #

ToPoint C Source # 
Instance details

Defined in Draw.Grid

Methods

toPoint :: C -> P2 Double Source #

type Diff C Source # 
Instance details

Defined in Data.GridShape

type Diff C = (Int, Int)
type Dual C Source # 
Instance details

Defined in Data.GridShape

type Dual C = N

data N Source #

Constructors

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

Defined in Data.GridShape

Methods

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

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

Ord N Source # 
Instance details

Defined in Data.GridShape

Methods

compare :: N -> N -> Ordering #

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

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

(>) :: N -> N -> Bool #

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

max :: N -> N -> N #

min :: N -> N -> N #

Show N Source # 
Instance details

Defined in Data.GridShape

Methods

showsPrec :: Int -> N -> ShowS #

show :: N -> String #

showList :: [N] -> ShowS #

AffineSpace N Source # 
Instance details

Defined in Data.GridShape

Associated Types

type Diff N :: * #

Methods

(.-.) :: N -> N -> Diff N #

(.+^) :: N -> Diff N -> N #

Dual2D N Source # 
Instance details

Defined in Data.GridShape

Associated Types

type Dual N :: * Source #

Methods

dualE' :: Edge' N -> Edge' (Dual N) Source #

ToCoord N Source # 
Instance details

Defined in Data.GridShape

Methods

toCoord :: N -> Coord Source #

FromCoord N Source # 
Instance details

Defined in Data.GridShape

Methods

fromCoord :: Coord -> N Source #

ToPoint N Source # 
Instance details

Defined in Draw.Grid

Methods

toPoint :: N -> P2 Double Source #

type Diff N Source # 
Instance details

Defined in Data.GridShape

type Diff N = (Int, Int)
type Dual N Source # 
Instance details

Defined in Data.GridShape

type Dual N = C

class FromCoord a where Source #

Minimal complete definition

fromCoord

Methods

fromCoord :: Coord -> a Source #

Instances
FromCoord N Source # 
Instance details

Defined in Data.GridShape

Methods

fromCoord :: Coord -> N Source #

FromCoord C Source # 
Instance details

Defined in Data.GridShape

Methods

fromCoord :: Coord -> C Source #

class ToCoord a where Source #

Minimal complete definition

toCoord

Methods

toCoord :: a -> Coord Source #

Instances
ToCoord N Source # 
Instance details

Defined in Data.GridShape

Methods

toCoord :: N -> Coord Source #

ToCoord C Source # 
Instance details

Defined in Data.GridShape

Methods

toCoord :: C -> Coord Source #

edge :: (AffineSpace a, Diff a ~ (Int, Int)) => a -> a -> Edge a Source #

edge' :: (AffineSpace a, Diff a ~ (Int, Int)) => a -> a -> Edge' a Source #

edgeBetween :: Dual' k => k -> k -> Edge (Dual k) Source #

edgeBetween' :: Dual' k => k -> k -> Edge' (Dual k) Source #

ends' :: (AffineSpace a, Diff a ~ (Int, Int)) => Edge' a -> (a, a) Source #

revEdge :: (AffineSpace a, Diff a ~ (Int, Int)) => Edge' a -> Edge' a Source #

edges :: (Dual' k, Foldable f) => f k -> (k -> Bool) -> ([Edge' (Dual k)], [Edge (Dual k)]) Source #

edges computes the outer and inner edges of a set of cells. The set is given via fold and membership predicate, the result is a pair (outer, inner) of lists of edges, where the outer edges are oriented such that the outside is to the left.

edgesM :: Dual' k => Map k a -> ([Edge' (Dual k)], [Edge (Dual k)]) Source #

ends :: (AffineSpace a, Diff a ~ (Int, Int)) => Edge a -> (a, a) Source #

unorient :: (AffineSpace a, Diff a ~ (Int, Int)) => Edge' a -> Edge a Source #

dualE :: Dual' a => Edge a -> Edge (Dual a) Source #

rows :: Map C a -> [[a]] Source #