LambdaHack-0.6.1.0: A game engine library for roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.PointArray

Description

Arrays, based on Data.Vector.Unboxed, indexed by Point.

Synopsis

Documentation

data GArray w c Source #

Arrays indexed by Point.

Constructors

Array 

Fields

Instances

(Eq w, Unbox w) => Eq (GArray w c) Source # 

Methods

(==) :: GArray w c -> GArray w c -> Bool #

(/=) :: GArray w c -> GArray w c -> Bool #

Show (GArray w c) Source # 

Methods

showsPrec :: Int -> GArray w c -> ShowS #

show :: GArray w c -> String #

showList :: [GArray w c] -> ShowS #

(Unbox w, Binary w) => Binary (GArray w c) Source # 

Methods

put :: GArray w c -> Put #

get :: Get (GArray w c) #

putList :: [GArray w c] -> Put #

type Array c = GArray Word8 c Source #

Arrays of, effectively, Word8, indexed by Point.

(!) :: (Unbox w, Enum w, Enum c) => GArray w c -> Point -> c Source #

Array lookup.

accessI :: Unbox w => GArray w c -> Int -> w Source #

(//) :: (Unbox w, Enum w, Enum c) => GArray w c -> [(Point, c)] -> GArray w c Source #

Construct an array updated with the association list.

replicateA :: (Unbox w, Enum w, Enum c) => X -> Y -> c -> GArray w c Source #

Create an array from a replicated element.

replicateMA :: (Unbox w, Enum w, Enum c, Monad m) => X -> Y -> m c -> m (GArray w c) Source #

Create an array from a replicated monadic action.

generateA :: (Unbox w, Enum w, Enum c) => X -> Y -> (Point -> c) -> GArray w c Source #

Create an array from a function.

generateMA :: (Unbox w, Enum w, Enum c, Monad m) => X -> Y -> (Point -> m c) -> m (GArray w c) Source #

Create an array from a monadic function.

unfoldrNA :: (Unbox w, Enum w, Enum c) => X -> Y -> (b -> (c, b)) -> b -> GArray w c Source #

sizeA :: GArray w c -> (X, Y) Source #

Content identifiers array size.

foldrA :: (Unbox w, Enum w, Enum c) => (c -> a -> a) -> a -> GArray w c -> a Source #

Fold right over an array.

foldrA' :: (Unbox w, Enum w, Enum c) => (c -> a -> a) -> a -> GArray w c -> a Source #

Fold right strictly over an array.

foldlA' :: (Unbox w, Enum w, Enum c) => (a -> c -> a) -> a -> GArray w c -> a Source #

Fold left strictly over an array.

ifoldrA :: (Unbox w, Enum w, Enum c) => (Point -> c -> a -> a) -> a -> GArray w c -> a Source #

Fold right over an array (function applied to each element and its index).

ifoldrA' :: (Unbox w, Enum w, Enum c) => (Point -> c -> a -> a) -> a -> GArray w c -> a Source #

Fold right strictly over an array (function applied to each element and its index).

ifoldlA' :: (Unbox w, Enum w, Enum c) => (a -> Point -> c -> a) -> a -> GArray w c -> a Source #

Fold left strictly over an array (function applied to each element and its index).

foldMA' :: (Monad m, Unbox w, Enum w, Enum c) => (a -> c -> m a) -> a -> GArray w c -> m a Source #

Fold monadically strictly over an array.

ifoldMA' :: (Monad m, Unbox w, Enum w, Enum c) => (a -> Point -> c -> m a) -> a -> GArray w c -> m a Source #

Fold monadically strictly over an array (function applied to each element and its index).

mapA :: (Unbox w1, Enum w1, Unbox w2, Enum w2, Enum c, Enum d) => (c -> d) -> GArray w1 c -> GArray w2 d Source #

Map over an array.

imapA :: (Unbox w1, Enum w1, Unbox w2, Enum w2, Enum c, Enum d) => (Point -> c -> d) -> GArray w1 c -> GArray w2 d Source #

Map over an array (function applied to each element and its index).

imapMA_ :: (Unbox w, Enum w, Enum c, Monad m) => (Point -> c -> m ()) -> GArray w c -> m () Source #

Map monadically over an array (function applied to each element and its index) and ignore the results.

safeSetA :: (Unbox w, Enum w, Enum c) => c -> GArray w c -> GArray w c Source #

Set all elements to the given value, in place, if possible.

unsafeSetA :: (Unbox w, Enum w, Enum c) => c -> GArray w c -> GArray w c Source #

Set all elements to the given value, in place.

unsafeUpdateA :: (Unbox w, Enum w, Enum c) => GArray w c -> [(Point, c)] -> () Source #

unsafeWriteA :: (Unbox w, Enum w, Enum c) => GArray w c -> Point -> c -> () Source #

unsafeWriteManyA :: (Unbox w, Enum w, Enum c) => GArray w c -> [Point] -> c -> () Source #

minIndexA :: (Unbox w, Ord w) => GArray w c -> Point Source #

Yield the point coordinates of a minimum element of the array. The array may not be empty.

minLastIndexA :: (Unbox w, Ord w) => GArray w c -> Point Source #

Yield the point coordinates of the last minimum element of the array. The array may not be empty.

minIndexesA :: (Unbox w, Enum w, Ord w) => GArray w c -> [Point] Source #

Yield the point coordinates of all the minimum elements of the array. The array may not be empty.

maxIndexA :: (Unbox w, Ord w) => GArray w c -> Point Source #

Yield the point coordinates of the first maximum element of the array. The array may not be empty.

maxLastIndexA :: (Unbox w, Ord w) => GArray w c -> Point Source #

Yield the point coordinates of the last maximum element of the array. The array may not be empty.

forceA :: Unbox w => GArray w c -> GArray w c Source #

Force the array not to retain any extra memory.

fromListA :: (Unbox w, Enum w, Enum c) => X -> Y -> [c] -> GArray w c Source #

toListA :: (Unbox w, Enum w, Enum c) => GArray w c -> [c] Source #