grid-2.0: Tools for working with regular grids\/graphs\/lattices.

Portabilityportable
Stabilityexperimental
Maintaineramy@nualeargais.ie
Safe HaskellSafe-Inferred

Math.Geometry.GridMap

Contents

Description

Ordered maps from tiles on a grid to values. This module is a wrapper around Grid and Map, in order to combine the functionality of grids and maps into a single type.

Synopsis

Differences between GridMap and Map.

Some functions in Data.Map have been replaced in GridMap. These changes are listed in the table below.

Map function    | corresponding GridMap function
----------------+-------------------------------
assocs          | toList
empty           | lazyGridMap g []
foldl           | fold
foldl'          | fold'
foldlWithKey    | foldWithKey
foldlWithKey'   | foldWithKey'
foldr           | fold
foldr'          | fold'
foldrWithKey    | foldWithKey
foldrWithKey'   | foldWithKey'
fromList        | lazyGridMap
fromListWithKey | lazyGridMap
fromListWith    | lazyGridMap
fromSet         | lazyGridMap
keys            | indices
member          | inGrid
notMember       | not inGrid
null            | empty
singleton       | lazyGridMap g [v]
size            | size, tileCount

The functions (\), alter, delete, deleteFindMax, deleteFindMin, deleteMax, deleteMin, difference, differenceWith, differenceWithKey, filter, filterWithKey, insert, insertLookupWithKey, insertWith, insertWithKey, intersection, intersectionWith, intersectionWithKey, isProperSubmapOf, isProperSubmapOfBy, isSubmapOf, isSubmapOf, isSubmapOfBy, mapEither, mapEitherWithKey, mapKeys, mapKeysWith, mapMaybe, mapMaybeWithKey, mergeWithKey, partition, partitionWithKey, split, splitLookup, traverseWithKey, union, unions, unionsWith, unionWith, unionWithKey, update, updateLookupWithKey and updateWithKey are not implemented because the resulting map might have different dimensions than the original, or because they combine maps of different dimensions. As a result, these functions may not be as useful for grid maps. If you need one of these functions, you can extract the map using toMap and apply the function from Data.Map to the result.

The functions deleteAt, elemAt, findIndex, findMax, findMin, fromAscList, fromAscListWith, fromAscListWithKey, fromDistinctAscList, lookupGE, lookupGT, lookupIndex, lookupLE, lookupLT, mapAccumRWithKey, mapKeysMonotonic, maxView, maxViewWithKey, minView, minViewWithKey, toAscList, toDescList, updateAt, updateMax, updateMaxWithKey, updateMin and updateMinWithKey are not implemented because they rely on a meaningful ordering of keys. While tile positions can be ordered (e.g., (1,2) < (2,1)), the ordering may not be relevant to grid maps. (Comparisons such as east of or south of may be more meaningful.) If you need one of these functions, you can extract the map using toMap and apply the function from Data.Map to the result.

The debugging functions showTree, showTreeWith and valid are not implemented. If you need one of these functions, you can extract the map using toMap and apply the function from Data.Map to the result.

Map type

data GridMap g k v Source

A Map from tile positions in a grid to values.

Instances

(Eq g, Eq k, Eq v) => Eq (GridMap g k v) 
(Show g, Show v) => Show (GridMap g k v) 
(Eq k, Grid g s k) => Grid (GridMap g k v) s k 

Construction

lazyGridMap :: (Ord k, Grid g s k) => g -> [v] -> GridMap g k vSource

Construct a grid map which is strict in the keys (tile positions), but lazy in the values.

Grid functions

indices :: Grid g s x => g -> [x]Source

Returns the indices of all tiles in a grid.

distance :: Grid g s x => x -> x -> g -> IntSource

distance a b returns the minimum number of moves required to get from a to b, 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.

size :: Grid g s x => g -> sSource

Returns the dimensions of the grid. For example, if g is a 4x3 rectangular grid, size g would return (4, 3), while tileCount g would return 12.

neighbours :: Grid g s x => x -> g -> [x]Source

neighbours x g returns the indices of the tiles in the grid g which are adjacent to the tile at x.

inGrid :: Grid g s x => x -> g -> BoolSource

x `'inGrid'` g returns true if the index x is contained within g, otherwise it returns false.

viewpoint :: Grid g s x => x -> g -> [(x, Int)]Source

viewpoint x g returns a list of pairs associating the index of each tile in g with its distance to the tile with index x. If x is not contained within g, the result is undefined.

tileCount :: Grid g s x => g -> IntSource

Returns the number of tiles in a grid. Compare with size.

empty :: Grid g s x => g -> BoolSource

Returns True if the number of tiles in a grid is zero, False otherwise.

nonEmpty :: Grid g s x => g -> BoolSource

Returns False if the number of tiles in a grid is zero, True otherwise.

Map functions

Operators

(!) :: Ord k => GridMap g k v -> k -> vSource

O(min(n,W)). Find the value at a tile position in the grid. Calls error when the element can not be found.

Query

lookup :: Ord k => k -> GridMap g k v -> Maybe vSource

O(min(n,W)). Lookup the value at a tile position in the grid map.

findWithDefault :: Ord k => v -> k -> GridMap g k v -> vSource

O(min(n,W)). The expression (findWithDefault def k map) returns the value at tile position k or returns def when the tile is not within the bounds of the grid map.

Update

adjust :: Ord k => (v -> v) -> k -> GridMap g k v -> GridMap g k vSource

O(min(n,W)). Adjust a value at a specific tile position. When the tile is not within the bounds of the grid map, the original grid map is returned.

adjustWithKey :: Ord k => (k -> v -> v) -> k -> GridMap g k v -> GridMap g k vSource

O(min(n,W)). Adjust a value at a specific key. When the tile is not within the bounds of the grid map, the original grid map is returned.

Map

map :: (a -> b) -> GridMap g k a -> GridMap g k bSource

O(n). Map a function over all values in the grid map.

mapWithKey :: (k -> a -> b) -> GridMap g k a -> GridMap g k bSource

O(n). Map a function over all values in the grid map.

mapAccum :: (a -> b -> (a, c)) -> a -> GridMap g k b -> (a, GridMap g k c)Source

O(n). The function mapAccum threads an accumulating argument through the grid map. WARNING: The order in which the elements are processed is not guaranteed.

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> GridMap g k b -> (a, GridMap g k c)Source

O(n). The function mapAccumWithKey threads an accumulating argument through the grid map. WARNING: The order in which the elements are processed is not guaranteed.

Folds

fold :: (a -> b -> a) -> a -> GridMap g k b -> aSource

O(n). Fold the values in the grid map using the given left-associative binary operator. WARNING: The order in which the elements are processed is not guaranteed.

foldWithKey :: (a -> k -> b -> a) -> a -> GridMap g k b -> aSource

O(n). Fold the keys and values in the grid map using the given left-associative binary operator. WARNING: The order in which the elements are processed is not guaranteed.

fold' :: (a -> b -> a) -> a -> GridMap g k b -> aSource

O(n). A strict version of fold.

foldWithKey' :: (a -> k -> b -> a) -> a -> GridMap g k b -> aSource

O(n). A strict version of foldWithKey.

Conversion

elems :: GridMap g k a -> [a]Source

O(n). Return all elements of the grid map. The order is not guaranteed.

keysSet :: GridMap g k a -> Set kSource

O(n*min(n,W)). The set of all tile positions in the grid map.

Lists

toList :: GridMap g k a -> [(k, a)]Source

O(n). Returns all key (tile position)/value pairs in the grid map.