LambdaHack-0.9.3.1: A game engine library for tactical squad ASCII roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.PointArray

Contents

Description

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

Synopsis

Documentation

class (Ord c, Eq (UnboxRep c), Ord (UnboxRep c), Bounded (UnboxRep c), Binary (UnboxRep c), Unbox (UnboxRep c)) => UnboxRepClass c where Source #

Associated Types

type UnboxRep c Source #

data Array c Source #

Arrays indexed by Point.

Constructors

Array 

Fields

Instances
UnboxRepClass c => Eq (Array c) Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray

Methods

(==) :: Array c -> Array c -> Bool #

(/=) :: Array c -> Array c -> Bool #

Show (Array c) Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray

Methods

showsPrec :: Int -> Array c -> ShowS #

show :: Array c -> String #

showList :: [Array c] -> ShowS #

UnboxRepClass c => Binary (Array c) Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray

Methods

put :: Array c -> Put #

get :: Get (Array c) #

putList :: [Array c] -> Put #

(!) :: UnboxRepClass c => Array c -> Point -> c Source #

Array lookup.

(//) :: UnboxRepClass c => Array c -> [(Point, c)] -> Array c Source #

Construct an array updated with the association list.

unsafeUpdateA :: UnboxRepClass c => Array c -> [(Point, c)] -> () Source #

unsafeWriteA :: UnboxRepClass c => Array c -> Point -> c -> () Source #

unsafeWriteManyA :: UnboxRepClass c => Array c -> [Point] -> c -> () Source #

replicateA :: UnboxRepClass c => X -> Y -> c -> Array c Source #

Create an array from a replicated element.

replicateMA :: (Monad m, UnboxRepClass c) => X -> Y -> m c -> m (Array c) Source #

Create an array from a replicated monadic action.

generateA :: UnboxRepClass c => X -> Y -> (Point -> c) -> Array c Source #

Create an array from a function.

generateMA :: (Monad m, UnboxRepClass c) => X -> Y -> (Point -> m c) -> m (Array c) Source #

Create an array from a monadic function.

unfoldrNA :: UnboxRepClass c => X -> Y -> (b -> (c, b)) -> b -> Array c Source #

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

Content identifiers array size.

foldrA :: UnboxRepClass c => (c -> a -> a) -> a -> Array c -> a Source #

Fold right over an array.

foldrA' :: UnboxRepClass c => (c -> a -> a) -> a -> Array c -> a Source #

Fold right strictly over an array.

foldlA' :: UnboxRepClass c => (a -> c -> a) -> a -> Array c -> a Source #

Fold left strictly over an array.

ifoldrA :: UnboxRepClass c => (Point -> c -> a -> a) -> a -> Array c -> a Source #

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

ifoldrA' :: UnboxRepClass c => (Point -> c -> a -> a) -> a -> Array c -> a Source #

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

ifoldlA' :: UnboxRepClass c => (a -> Point -> c -> a) -> a -> Array c -> a Source #

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

foldMA' :: (Monad m, UnboxRepClass c) => (a -> c -> m a) -> a -> Array c -> m a Source #

Fold monadically strictly over an array.

ifoldMA' :: (Monad m, UnboxRepClass c) => (a -> Point -> c -> m a) -> a -> Array c -> m a Source #

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

mapA :: (UnboxRepClass c, UnboxRepClass d) => (c -> d) -> Array c -> Array d Source #

Map over an array.

imapA :: (UnboxRepClass c, UnboxRepClass d) => (Point -> c -> d) -> Array c -> Array d Source #

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

imapMA_ :: (Monad m, UnboxRepClass c) => (Point -> c -> m ()) -> Array c -> m () Source #

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

safeSetA :: UnboxRepClass c => c -> Array c -> Array c Source #

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

unsafeSetA :: UnboxRepClass c => c -> Array c -> Array c Source #

Set all elements to the given value, in place.

minIndexA :: UnboxRepClass c => Array c -> Point Source #

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

minLastIndexA :: UnboxRepClass c => Array c -> Point Source #

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

minIndexesA :: UnboxRepClass c => Array c -> [Point] Source #

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

maxIndexA :: UnboxRepClass c => Array c -> Point Source #

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

maxIndexByA :: UnboxRepClass c => (c -> c -> Ordering) -> Array c -> Point Source #

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

maxLastIndexA :: UnboxRepClass c => Array c -> Point Source #

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

forceA :: UnboxRepClass c => Array c -> Array c Source #

Force the array not to retain any extra memory.

fromListA :: UnboxRepClass c => X -> Y -> [c] -> Array c Source #

Internal operations