Copyright | (c) Amy de Buitléir 2012-2019 |
---|---|
License | BSD-style |
Maintainer | amy@nualeargais.ie |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
A module containing private Grid
internals. Most developers should
use Grid
instead. This module is subject to change without notice.
Synopsis
- class Grid g where
- type Index g
- type Direction g
- indices :: g -> [Index g]
- distance :: g -> Index g -> Index g -> Int
- minDistance :: g -> [Index g] -> Index g -> Int
- neighbours :: Eq (Index g) => g -> Index g -> [Index g]
- neighboursOfSet :: Eq (Index g) => g -> [Index g] -> [Index g]
- neighbour :: (Eq (Index g), Eq (Direction g)) => g -> Index g -> Direction g -> Maybe (Index g)
- numNeighbours :: Eq (Index g) => g -> Index g -> Int
- contains :: Eq (Index g) => g -> Index g -> Bool
- tileCount :: g -> Int
- null :: g -> Bool
- nonNull :: g -> Bool
- edges :: Eq (Index g) => g -> [(Index g, Index g)]
- viewpoint :: g -> Index g -> [(Index g, Int)]
- isAdjacent :: g -> Index g -> Index g -> Bool
- adjacentTilesToward :: Eq (Index g) => g -> Index g -> Index g -> [Index g]
- minimalPaths :: Eq (Index g) => g -> Index g -> Index g -> [[Index g]]
- directionTo :: g -> Index g -> Index g -> [Direction g]
- defaultMinDistance :: g -> [Index g] -> Index g -> Int
- defaultNeighbours :: g -> Index g -> [Index g]
- defaultNeighboursOfSet :: Eq (Index g) => g -> [Index g] -> [Index g]
- defaultNeighbour :: (Eq (Index g), Eq (Direction g)) => g -> Index g -> Direction g -> Maybe (Index g)
- defaultTileCount :: g -> Int
- defaultEdges :: Eq (Index g) => g -> [(Index g, Index g)]
- defaultIsAdjacent :: g -> Index g -> Index g -> Bool
- defaultAdjacentTilesToward :: Eq (Index g) => g -> Index g -> Index g -> [Index g]
- defaultMinimalPaths :: Eq (Index g) => g -> Index g -> Index g -> [[Index g]]
- class Grid g => FiniteGrid g where
- type Size g
- size :: g -> Size g
- maxPossibleDistance :: g -> Int
- class Grid g => BoundedGrid g where
- tileSideCount :: g -> Int
- boundary :: Eq (Index g) => g -> [Index g]
- isBoundary :: Eq (Index g) => g -> Index g -> Bool
- centre :: Eq (Index g) => g -> [Index g]
- isCentre :: Eq (Index g) => g -> Index g -> Bool
- defaultBoundary :: Eq (Index g) => g -> [Index g]
- defaultIsBoundary :: Eq (Index g) => g -> Index g -> Bool
- defaultCentre :: Eq (Index g) => g -> [Index g]
- defaultIsCentre :: Eq (Index g) => g -> Index g -> Bool
- class Grid g => WrappedGrid g where
- neighboursBasedOn :: (Eq (Index u), Grid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> [Index g]
- distanceBasedOn :: (Eq (Index g), Grid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> Index g -> Int
- directionToBasedOn :: (Eq (Index g), Eq (Direction g), Grid g, Grid u, Index g ~ Index u, Direction g ~ Direction u) => u -> g -> Index g -> Index g -> [Direction g]
- neighboursWrappedBasedOn :: (Eq (Index g), WrappedGrid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> [Index g]
- neighbourWrappedBasedOn :: (Eq (Index g), Eq (Direction g), WrappedGrid g, Grid u, Index g ~ Index u, Direction g ~ Direction u) => u -> g -> Index g -> Direction g -> Maybe (Index g)
- distanceWrappedBasedOn :: (Eq (Index g), WrappedGrid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> Index g -> Int
- directionToWrappedBasedOn :: (Eq (Index g), Eq (Direction g), WrappedGrid g, Grid u, Index g ~ Index u, Direction g ~ Direction u) => u -> g -> Index g -> Index g -> [Direction g]
- sameEdge :: Eq t => (t, t) -> (t, t) -> Bool
- adjacentEdges :: (Grid g, Eq (Index g)) => Index g -> g -> [(Index g, Index g)]
- cartesianIndices :: (Enum r, Enum c, Num r, Num c, Ord r, Ord c) => (r, c) -> [(c, r)]
- cartesianCentre :: (Int, Int) -> [(Int, Int)]
- cartesianMidpoints :: Int -> [Int]
Documentation
A regular arrangement of tiles.
Minimal complete definition:
, Index
, Direction
,
indices
, distance
.directionTo
indices :: g -> [Index g] Source #
Returns the indices of all tiles in a grid.
distance :: g -> Index g -> Index g -> Int Source #
returns the minimum number of moves required
to get from the tile at index distance
g a ba
to the tile at index b
in
grid g
, moving between adjacent tiles at each step. (Two tiles
are adjacent if they share an edge.) If a
or b
are not
contained within g
, the result is undefined.
minDistance :: g -> [Index g] -> Index g -> Int Source #
returns the minimum number of moves
required to get from any of the tiles at indices minDistance
g bs abs
to the tile
at index a
in grid g
, moving between adjacent tiles at each
step. (Two tiles are adjacent if they share an edge.) If a
or
any of bs
are not contained within g
, the result is
undefined.
neighbours :: Eq (Index g) => g -> Index g -> [Index g] Source #
returns the indices of the tiles in the grid
neighbours
g ag
which are adjacent to the tile with index a
.
neighboursOfSet :: Eq (Index g) => g -> [Index g] -> [Index g] Source #
returns the indices of the tiles in the
grid neighboursOfSet
g asg
which are adjacent to any of the tiles with index in
as
.
neighbour :: (Eq (Index g), Eq (Direction g)) => g -> Index g -> Direction g -> Maybe (Index g) Source #
returns the indices of the tile in the grid
neighbour
g d ag
which is adjacent to the tile with index a
, in the
direction d
.
numNeighbours :: Eq (Index g) => g -> Index g -> Int Source #
returns the number of tiles in the grid
numNeighbours
g ag
which are adjacent to the tile with index a
.
contains :: Eq (Index g) => g -> Index g -> Bool Source #
g `
returns contains'
aTrue
if the index a
is contained
within the grid g
, otherwise it returns false.
tileCount :: g -> Int Source #
Returns the number of tiles in a grid. Compare with
.size
Returns True
if the number of tiles in a grid is zero, False
otherwise.
Returns False
if the number of tiles in a grid is zero, True
otherwise.
edges :: Eq (Index g) => g -> [(Index g, Index g)] Source #
A list of all edges in a grid, where the edges are represented by a pair of indices of adjacent tiles.
viewpoint :: g -> Index g -> [(Index g, Int)] Source #
returns a list of pairs associating the index
of each tile in viewpoint
g ag
with its distance to the tile with index a
.
If a
is not contained within g
, the result is undefined.
isAdjacent :: g -> Index g -> Index g -> Bool Source #
returns isAdjacent
g a bTrue
if the tile at index a
is
adjacent to the tile at index b
in g
. (Two tiles are adjacent
if they share an edge.) If a
or b
are not contained within
g
, the result is undefined.
adjacentTilesToward :: Eq (Index g) => g -> Index g -> Index g -> [Index g] Source #
returns the indices of all tiles
which are neighbours of the tile at index adjacentTilesToward
g a ba
, and which are
closer to the tile at b
than a
is. In other words, it returns
the possible next steps on a minimal path from a
to b
. If a
or b
are not contained within g
, or if there is no path from
a
to b
(e.g., a disconnected grid), the result is undefined.
minimalPaths :: Eq (Index g) => g -> Index g -> Index g -> [[Index g]] Source #
returns a list of all minimal paths from
the tile at index minimalPaths
g a ba
to the tile at index b
in grid g
. A
path is a sequence of tiles where each tile in the sequence is
adjacent to the previous one. (Two tiles are adjacent if they
share an edge.) If a
or b
are not contained within g
, the
result is undefined.
Tip: The default implementation of this function calls
. If you want to use a custom algorithm,
consider modifying adjacentTilesToward
instead of
adjacentTilesToward
.minimalPaths
directionTo :: g -> Index g -> Index g -> [Direction g] Source #
returns the direction(s) of the next
tile(s) in a minimal path from the tile at index directionTo
g a ba
to the
tile at index b
in grid g
.
defaultMinDistance :: g -> [Index g] -> Index g -> Int Source #
defaultNeighbours :: g -> Index g -> [Index g] Source #
defaultNeighboursOfSet :: Eq (Index g) => g -> [Index g] -> [Index g] Source #
defaultNeighbour :: (Eq (Index g), Eq (Direction g)) => g -> Index g -> Direction g -> Maybe (Index g) Source #
defaultTileCount :: g -> Int Source #
defaultEdges :: Eq (Index g) => g -> [(Index g, Index g)] Source #
defaultIsAdjacent :: g -> Index g -> Index g -> Bool Source #
defaultAdjacentTilesToward :: Eq (Index g) => g -> Index g -> Index g -> [Index g] Source #
defaultMinimalPaths :: Eq (Index g) => g -> Index g -> Index g -> [[Index g]] Source #
Instances
class Grid g => FiniteGrid g where Source #
A regular arrangement of tiles where the number of tiles is finite.
Minimal complete definition:
, size
.maxPossibleDistance
Returns the dimensions of the grid.
For example, if g
is a 4x3 rectangular grid,
would
return size
g(4, 3)
, while
would return tileCount
g12
.
maxPossibleDistance :: g -> Int Source #
Returns the largest possible distance between two tiles in the grid.
Instances
class Grid g => BoundedGrid g where Source #
A regular arrangement of tiles with an edge.
Minimal complete definition:
.tileSideCount
tileSideCount :: g -> Int Source #
Returns the number of sides a tile has
boundary :: Eq (Index g) => g -> [Index g] Source #
Returns a the indices of all the tiles at the boundary of a grid.
isBoundary :: Eq (Index g) => g -> Index g -> Bool Source #
' returns isBoundary
g aTrue
if the tile with index a
is
on a boundary of g
, False
otherwise. (Corner tiles are also
boundary tiles.)
centre :: Eq (Index g) => g -> [Index g] Source #
Returns the index of the tile(s) that require the maximum number of moves to reach the nearest boundary tile. A grid may have more than one central tile (e.g., a rectangular grid with an even number of rows and columns will have four central tiles).
isCentre :: Eq (Index g) => g -> Index g -> Bool Source #
' returns isCentre
g aTrue
if the tile with index a
is
a centre tile of g
, False
otherwise.
defaultBoundary :: Eq (Index g) => g -> [Index g] Source #
defaultIsBoundary :: Eq (Index g) => g -> Index g -> Bool Source #
defaultCentre :: Eq (Index g) => g -> [Index g] Source #
defaultIsCentre :: Eq (Index g) => g -> Index g -> Bool Source #
Instances
class Grid g => WrappedGrid g where Source #
A regular arrangement of tiles where the boundaries are joined.
Minimal complete definition:
and normalise
.denormalise
normalise :: g -> Index g -> Index g Source #
returns the "normal" indices for normalise
g aa
.
TODO: need a clearer description and an illustration.
denormalise :: g -> Index g -> [Index g] Source #
returns all of the indices in denormalise
g aa
's
translation group. In other words, it returns a
plus the
indices obtained by translating a
in each direction by the
extent of the grid along that direction.
TODO: need a clearer description and an illustration.
Instances
neighboursBasedOn :: (Eq (Index u), Grid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> [Index g] Source #
distanceBasedOn :: (Eq (Index g), Grid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> Index g -> Int Source #
directionToBasedOn :: (Eq (Index g), Eq (Direction g), Grid g, Grid u, Index g ~ Index u, Direction g ~ Direction u) => u -> g -> Index g -> Index g -> [Direction g] Source #
neighboursWrappedBasedOn :: (Eq (Index g), WrappedGrid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> [Index g] Source #
neighbourWrappedBasedOn :: (Eq (Index g), Eq (Direction g), WrappedGrid g, Grid u, Index g ~ Index u, Direction g ~ Direction u) => u -> g -> Index g -> Direction g -> Maybe (Index g) Source #
distanceWrappedBasedOn :: (Eq (Index g), WrappedGrid g, Grid u, Index g ~ Index u) => u -> g -> Index g -> Index g -> Int Source #
directionToWrappedBasedOn :: (Eq (Index g), Eq (Direction g), WrappedGrid g, Grid u, Index g ~ Index u, Direction g ~ Direction u) => u -> g -> Index g -> Index g -> [Direction g] Source #
cartesianMidpoints :: Int -> [Int] Source #