grid-7.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

Map classes and types

class (Grid (BaseGrid gm v), Foldable gm) => GridMap gm v whereSource

A regular arrangement of tiles, having a value associated with each tile. Minimal complete definition: toMap, toGrid, adjustWithKey, mapWithKey.

Note: Some of the methods have an Ord constraint on the grid index. This is purely to make it easier to write implementations. While tile positions can be ordered (e.g., (1,2) < (2,1)), the ordering may not be particularly meaningful. (Comparisons such as east of or south of may be more sensible.) However, it is convenient to write implementations of this class using Data.Map, with the grid indices as keys. Many of the functions in Data.Map impose the Ord constraint on map keys, so we'll live with it. In summary, to use some methods in this class, your grid indices must be orderable.

Associated Types

type BaseGrid gm v Source

Methods

(!) :: (k ~ Index (BaseGrid gm v), Ord k) => gm v -> k -> vSource

Find the value at a tile position in the grid.

toMap :: k ~ Index (BaseGrid gm v) => gm v -> Map k vSource

Returns a map of grid indices to values.

toGrid :: gm v -> BaseGrid gm vSource

Returns the grid on which this map is based.

toList :: k ~ Index (BaseGrid gm v) => gm v -> [(k, v)]Source

Convert the map to a list of key/value pairs.

lookup :: (k ~ Index (BaseGrid gm v), Ord k) => k -> gm v -> Maybe vSource

Lookup the value at a tile position in the grid map.

adjust :: (k ~ Index (BaseGrid gm v), Ord k) => (v -> v) -> k -> gm v -> gm vSource

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 :: (k ~ Index (BaseGrid gm v), Ord k) => (k -> v -> v) -> k -> gm v -> gm vSource

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.

findWithDefault :: (k ~ Index (BaseGrid gm v), Ord k) => v -> k -> gm v -> vSource

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.

elems :: gm v -> [v]Source

Returns all values in the map

map :: (GridMap gm v2, Index (BaseGrid gm v) ~ Index (BaseGrid gm v2)) => (v -> v2) -> gm v -> gm v2Source

Map a function over all values in the map.

mapWithKey :: (k ~ Index (BaseGrid gm v), k ~ Index (BaseGrid gm v2), GridMap gm v2) => (k -> v -> v2) -> gm v -> gm v2Source

Map a function over all values in the map.

Instances

Grid g => GridMap (LGridMap g) v 

Folds

foldr :: (a -> b -> b) -> b -> Map k a -> b

O(n). Fold the values in the map using the given right-associative binary operator, such that foldr f z == foldr f z . elems.

For example,

 elems map = foldr (:) [] map
 let f a len = len + (length a)
 foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4

foldr' :: (a -> b -> b) -> b -> Map k a -> b

O(n). A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldl :: (a -> b -> a) -> a -> Map k b -> a

O(n). Fold the values in the map using the given left-associative binary operator, such that foldl f z == foldl f z . elems.

For example,

 elems = reverse . foldl (flip (:)) []
 let f len a = len + (length a)
 foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4

foldl' :: (a -> b -> a) -> a -> Map k b -> a

O(n). A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

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
--------------------+----------------------------------------------
!                   | !
\\                  | See note 1
empty               | lazyGridMap g []
findWithDefault     | findWithDefault
insert              | See notes 1, 2
lookup              | lookup
lookupLE            | See notes 1, 3
lookupLT            | See notes 1, 3
lookupGE            | See notes 1, 3
lookupGT            | See notes 1, 3
member              | contains
notMember           | not contains
null                | null
singleton           | lazyGridMap g [v]
size                | size, tileCount
insert              | See notes 1, 2
insertWith          | See notes 1, 2
insertWithKey       | See notes 1, 2
insertLookupWithKey | See notes 1, 2
delete              | See notes 1, 2
adjust              | adjust
adjustWithKey       | adjustWithKey
update              | See notes 1, 2
updateWithKey       | See notes 1, 2
updateLookupWithKey | See notes 1, 2
alter               | See notes 1, 2
union               | See notes 1, 2
unionWith           | See notes 1, 2
unionWithKey        | See notes 1, 2
unions              | See notes 1, 2
unionsWith          | See notes 1, 2
difference          | See notes 1, 2
differenceWith      | See notes 1, 2
differenceWithKey   | See notes 1, 2
intersection        | See notes 1, 2
intersectionWith    | See notes 1, 2
intersectionWithKey | See notes 1, 2
mergeWithKey        | See notes 1, 2
M.map               | fmap, or see note 1
mapWithKey          | See note 1
traverseWithKey     | See notes 1, 2
mapAccum            | See note 1
mapAccumWithKey     | See note 1
mapAccumRWithKey    | See note 1
mapKeys             | See note 1
mapKeysWith         | See note 1
mapKeysMonotonic    | See note 1
foldr               | See note 1
foldl               | See note 1
foldrWithKey        | See note 1
foldlWithKey        | See note 1
foldr'              | See note 1
foldl'              | See note 1
foldrWithKey'       | See note 1
foldlWithKey'       | See note 1
elems               | elems
keys                | indices
assocs              | See note 1
keysSet             | See note 1
fromSet             | lazyGridMap
toList              | See note 1
fromList            | lazyGridMap
fromListWithKey     | lazyGridMap
fromListWith        | lazyGridMap
toAscList           | See notes 1, 3
toDescList          | See notes 1, 3
fromAscList         | See notes 1, 3
fromAscListWith     | See notes 1, 3
fromAscListWithKey  | See notes 1, 3
fromDistinctAscList | See notes 1, 3
filter              | See notes 1, 2
filterWithKey       | See notes 1, 2
partition           | See notes 1, 2
partitionWithKey    | See notes 1, 2
mapMaybe            | See notes 1, 2
mapMaybeWithKey     | See notes 1, 2
mapEither           | See notes 1, 2
mapEitherWithKey    | See notes 1, 2
split               | See notes 1, 2
splitLookup         | See notes 1, 2
isSubmapOf          | See note 1
isSubmapOfBy        | See note 1
isProperSubmapOf    | See note 1
isProperSubmapOfBy  | See note 1
lookupIndex         | See note 1
findIndex           | See note 1
elemAt              | See note 1
updateAt            | See note 1
deleteAt            | See notes 1, 2
findMin             | See notes 1, 3
findMax             | See notes 1, 3
deleteMin           | See notes 1, 2, 3
deleteMax           | See notes 1, 2, 3
deleteFindMin       | See notes 1, 2, 3
deleteFindMax       | See notes 1, 2, 3
updateMin           | See notes 1, 2, 3
updateMax           | See notes 1, 2, 3
updateMinWithKey    | See notes 1, 2, 3
updateMaxWithKey    | See notes 1, 2, 3
minView             | See notes 1, 3
maxView             | See notes 1, 3
minViewWithKey      | See notes 1, 2, 3
maxViewWithKey      | See notes 1, 2, 3
showTree            | See note 1
showTreeWith        | See note 1
valid               | See note 1

Notes:

  1. You can extract the map using toMap and apply the function from Data.Map to the result.
  2. Not implemented because the resulting map might have different dimensions than the original input GridMap(s). However, you can extract the map using toMap and apply the function from Data.Map to the result.
  3. Not implemented because, although tile positions can be ordered (e.g., (1,2) < (2,1)), the ordering may not be meaningful for grid maps. Comparisons such as east of or south of may be more useful. However, you can extract the map using toMap and apply the function from Data.Map to the result.