array-0.5.6.0: Mutable and immutable arrays
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilitynon-portable (uses Data.Array.Base)
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Array.IArray

Description

Immutable arrays, with an overloaded interface. For array types which can be used with this interface, see the Array type exported by this module and the Data.Array.Unboxed module. Other packages, such as diffarray, also provide arrays using this interface.

Synopsis

Array classes

class IArray a e Source #

Class of immutable array types.

An array type has the form (a i e) where a is the array type constructor (kind * -> * -> *), i is the index type (a member of the class Ix), and e is the element type. The IArray class is parameterised over both a and e, so that instances specialised to certain element types can be defined.

Minimal complete definition

bounds, numElements, unsafeArray, unsafeAt

Instances

Instances details
IArray UArray Int16 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int16 -> (i, i) Source #

numElements :: Ix i => UArray i Int16 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Int16)] -> UArray i Int16 Source #

unsafeAt :: Ix i => UArray i Int16 -> Int -> Int16 Source #

unsafeReplace :: Ix i => UArray i Int16 -> [(Int, Int16)] -> UArray i Int16 Source #

unsafeAccum :: Ix i => (Int16 -> e' -> Int16) -> UArray i Int16 -> [(Int, e')] -> UArray i Int16 Source #

unsafeAccumArray :: Ix i => (Int16 -> e' -> Int16) -> Int16 -> (i, i) -> [(Int, e')] -> UArray i Int16 Source #

IArray UArray Int32 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int32 -> (i, i) Source #

numElements :: Ix i => UArray i Int32 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Int32)] -> UArray i Int32 Source #

unsafeAt :: Ix i => UArray i Int32 -> Int -> Int32 Source #

unsafeReplace :: Ix i => UArray i Int32 -> [(Int, Int32)] -> UArray i Int32 Source #

unsafeAccum :: Ix i => (Int32 -> e' -> Int32) -> UArray i Int32 -> [(Int, e')] -> UArray i Int32 Source #

unsafeAccumArray :: Ix i => (Int32 -> e' -> Int32) -> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32 Source #

IArray UArray Int64 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int64 -> (i, i) Source #

numElements :: Ix i => UArray i Int64 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64 Source #

unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64 Source #

unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64 Source #

unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64 Source #

unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64 Source #

IArray UArray Int8 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int8 -> (i, i) Source #

numElements :: Ix i => UArray i Int8 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Int8)] -> UArray i Int8 Source #

unsafeAt :: Ix i => UArray i Int8 -> Int -> Int8 Source #

unsafeReplace :: Ix i => UArray i Int8 -> [(Int, Int8)] -> UArray i Int8 Source #

unsafeAccum :: Ix i => (Int8 -> e' -> Int8) -> UArray i Int8 -> [(Int, e')] -> UArray i Int8 Source #

unsafeAccumArray :: Ix i => (Int8 -> e' -> Int8) -> Int8 -> (i, i) -> [(Int, e')] -> UArray i Int8 Source #

IArray UArray Word16 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word16 -> (i, i) Source #

numElements :: Ix i => UArray i Word16 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Word16)] -> UArray i Word16 Source #

unsafeAt :: Ix i => UArray i Word16 -> Int -> Word16 Source #

unsafeReplace :: Ix i => UArray i Word16 -> [(Int, Word16)] -> UArray i Word16 Source #

unsafeAccum :: Ix i => (Word16 -> e' -> Word16) -> UArray i Word16 -> [(Int, e')] -> UArray i Word16 Source #

unsafeAccumArray :: Ix i => (Word16 -> e' -> Word16) -> Word16 -> (i, i) -> [(Int, e')] -> UArray i Word16 Source #

IArray UArray Word32 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word32 -> (i, i) Source #

numElements :: Ix i => UArray i Word32 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32 Source #

unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32 Source #

unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32 Source #

unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32 Source #

unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32 Source #

IArray UArray Word64 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word64 -> (i, i) Source #

numElements :: Ix i => UArray i Word64 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64 Source #

unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64 Source #

unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64 Source #

unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64 Source #

unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64 Source #

IArray UArray Word8 Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word8 -> (i, i) Source #

numElements :: Ix i => UArray i Word8 -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8 Source #

unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8 Source #

unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8 Source #

unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8 Source #

unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8 Source #

IArray UArray Bool Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Bool -> (i, i) Source #

numElements :: Ix i => UArray i Bool -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Bool)] -> UArray i Bool Source #

unsafeAt :: Ix i => UArray i Bool -> Int -> Bool Source #

unsafeReplace :: Ix i => UArray i Bool -> [(Int, Bool)] -> UArray i Bool Source #

unsafeAccum :: Ix i => (Bool -> e' -> Bool) -> UArray i Bool -> [(Int, e')] -> UArray i Bool Source #

unsafeAccumArray :: Ix i => (Bool -> e' -> Bool) -> Bool -> (i, i) -> [(Int, e')] -> UArray i Bool Source #

IArray UArray Char Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Char -> (i, i) Source #

numElements :: Ix i => UArray i Char -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Char)] -> UArray i Char Source #

unsafeAt :: Ix i => UArray i Char -> Int -> Char Source #

unsafeReplace :: Ix i => UArray i Char -> [(Int, Char)] -> UArray i Char Source #

unsafeAccum :: Ix i => (Char -> e' -> Char) -> UArray i Char -> [(Int, e')] -> UArray i Char Source #

unsafeAccumArray :: Ix i => (Char -> e' -> Char) -> Char -> (i, i) -> [(Int, e')] -> UArray i Char Source #

IArray UArray Double Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Double -> (i, i) Source #

numElements :: Ix i => UArray i Double -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Double)] -> UArray i Double Source #

unsafeAt :: Ix i => UArray i Double -> Int -> Double Source #

unsafeReplace :: Ix i => UArray i Double -> [(Int, Double)] -> UArray i Double Source #

unsafeAccum :: Ix i => (Double -> e' -> Double) -> UArray i Double -> [(Int, e')] -> UArray i Double Source #

unsafeAccumArray :: Ix i => (Double -> e' -> Double) -> Double -> (i, i) -> [(Int, e')] -> UArray i Double Source #

IArray UArray Float Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Float -> (i, i) Source #

numElements :: Ix i => UArray i Float -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Float)] -> UArray i Float Source #

unsafeAt :: Ix i => UArray i Float -> Int -> Float Source #

unsafeReplace :: Ix i => UArray i Float -> [(Int, Float)] -> UArray i Float Source #

unsafeAccum :: Ix i => (Float -> e' -> Float) -> UArray i Float -> [(Int, e')] -> UArray i Float Source #

unsafeAccumArray :: Ix i => (Float -> e' -> Float) -> Float -> (i, i) -> [(Int, e')] -> UArray i Float Source #

IArray UArray Int Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Int -> (i, i) Source #

numElements :: Ix i => UArray i Int -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Int)] -> UArray i Int Source #

unsafeAt :: Ix i => UArray i Int -> Int -> Int Source #

unsafeReplace :: Ix i => UArray i Int -> [(Int, Int)] -> UArray i Int Source #

unsafeAccum :: Ix i => (Int -> e' -> Int) -> UArray i Int -> [(Int, e')] -> UArray i Int Source #

unsafeAccumArray :: Ix i => (Int -> e' -> Int) -> Int -> (i, i) -> [(Int, e')] -> UArray i Int Source #

IArray UArray Word Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Word -> (i, i) Source #

numElements :: Ix i => UArray i Word -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Word)] -> UArray i Word Source #

unsafeAt :: Ix i => UArray i Word -> Int -> Word Source #

unsafeReplace :: Ix i => UArray i Word -> [(Int, Word)] -> UArray i Word Source #

unsafeAccum :: Ix i => (Word -> e' -> Word) -> UArray i Word -> [(Int, e')] -> UArray i Word Source #

unsafeAccumArray :: Ix i => (Word -> e' -> Word) -> Word -> (i, i) -> [(Int, e')] -> UArray i Word Source #

IArray Array e Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => Array i e -> (i, i) Source #

numElements :: Ix i => Array i e -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> Array i e Source #

unsafeAt :: Ix i => Array i e -> Int -> e Source #

unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i e Source #

unsafeAccum :: Ix i => (e -> e' -> e) -> Array i e -> [(Int, e')] -> Array i e Source #

unsafeAccumArray :: Ix i => (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> Array i e Source #

IArray UArray (FunPtr a) Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i (FunPtr a) -> (i, i) Source #

numElements :: Ix i => UArray i (FunPtr a) -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, FunPtr a)] -> UArray i (FunPtr a) Source #

unsafeAt :: Ix i => UArray i (FunPtr a) -> Int -> FunPtr a Source #

unsafeReplace :: Ix i => UArray i (FunPtr a) -> [(Int, FunPtr a)] -> UArray i (FunPtr a) Source #

unsafeAccum :: Ix i => (FunPtr a -> e' -> FunPtr a) -> UArray i (FunPtr a) -> [(Int, e')] -> UArray i (FunPtr a) Source #

unsafeAccumArray :: Ix i => (FunPtr a -> e' -> FunPtr a) -> FunPtr a -> (i, i) -> [(Int, e')] -> UArray i (FunPtr a) Source #

IArray UArray (Ptr a) Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i (Ptr a) -> (i, i) Source #

numElements :: Ix i => UArray i (Ptr a) -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, Ptr a)] -> UArray i (Ptr a) Source #

unsafeAt :: Ix i => UArray i (Ptr a) -> Int -> Ptr a Source #

unsafeReplace :: Ix i => UArray i (Ptr a) -> [(Int, Ptr a)] -> UArray i (Ptr a) Source #

unsafeAccum :: Ix i => (Ptr a -> e' -> Ptr a) -> UArray i (Ptr a) -> [(Int, e')] -> UArray i (Ptr a) Source #

unsafeAccumArray :: Ix i => (Ptr a -> e' -> Ptr a) -> Ptr a -> (i, i) -> [(Int, e')] -> UArray i (Ptr a) Source #

IArray UArray (StablePtr a) Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i (StablePtr a) -> (i, i) Source #

numElements :: Ix i => UArray i (StablePtr a) -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, StablePtr a)] -> UArray i (StablePtr a) Source #

unsafeAt :: Ix i => UArray i (StablePtr a) -> Int -> StablePtr a Source #

unsafeReplace :: Ix i => UArray i (StablePtr a) -> [(Int, StablePtr a)] -> UArray i (StablePtr a) Source #

unsafeAccum :: Ix i => (StablePtr a -> e' -> StablePtr a) -> UArray i (StablePtr a) -> [(Int, e')] -> UArray i (StablePtr a) Source #

unsafeAccumArray :: Ix i => (StablePtr a -> e' -> StablePtr a) -> StablePtr a -> (i, i) -> [(Int, e')] -> UArray i (StablePtr a) Source #

module Data.Ix

Immutable non-strict (boxed) arrays

data Array i e #

The type of immutable non-strict (boxed) arrays with indices in i and elements in e.

Instances

Instances details
IArray Array e Source # 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => Array i e -> (i, i) Source #

numElements :: Ix i => Array i e -> Int Source #

unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> Array i e Source #

unsafeAt :: Ix i => Array i e -> Int -> e Source #

unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i e Source #

unsafeAccum :: Ix i => (e -> e' -> e) -> Array i e -> [(Int, e')] -> Array i e Source #

unsafeAccumArray :: Ix i => (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] -> Array i e Source #

Foldable (Array i)

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Array i m -> m #

foldMap :: Monoid m => (a -> m) -> Array i a -> m #

foldMap' :: Monoid m => (a -> m) -> Array i a -> m #

foldr :: (a -> b -> b) -> b -> Array i a -> b #

foldr' :: (a -> b -> b) -> b -> Array i a -> b #

foldl :: (b -> a -> b) -> b -> Array i a -> b #

foldl' :: (b -> a -> b) -> b -> Array i a -> b #

foldr1 :: (a -> a -> a) -> Array i a -> a #

foldl1 :: (a -> a -> a) -> Array i a -> a #

toList :: Array i a -> [a] #

null :: Array i a -> Bool #

length :: Array i a -> Int #

elem :: Eq a => a -> Array i a -> Bool #

maximum :: Ord a => Array i a -> a #

minimum :: Ord a => Array i a -> a #

sum :: Num a => Array i a -> a #

product :: Num a => Array i a -> a #

Ix i => Traversable (Array i)

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Array i a -> f (Array i b) #

sequenceA :: Applicative f => Array i (f a) -> f (Array i a) #

mapM :: Monad m => (a -> m b) -> Array i a -> m (Array i b) #

sequence :: Monad m => Array i (m a) -> m (Array i a) #

Functor (Array i)

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

fmap :: (a -> b) -> Array i a -> Array i b #

(<$) :: a -> Array i b -> Array i a #

(Ix a, Read a, Read b) => Read (Array a b)

Since: base-2.1

Instance details

Defined in GHC.Read

(Ix a, Show a, Show b) => Show (Array a b)

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

showsPrec :: Int -> Array a b -> ShowS #

show :: Array a b -> String #

showList :: [Array a b] -> ShowS #

(Ix i, Eq e) => Eq (Array i e)

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

(==) :: Array i e -> Array i e -> Bool #

(/=) :: Array i e -> Array i e -> Bool #

(Ix i, Ord e) => Ord (Array i e)

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

compare :: Array i e -> Array i e -> Ordering #

(<) :: Array i e -> Array i e -> Bool #

(<=) :: Array i e -> Array i e -> Bool #

(>) :: Array i e -> Array i e -> Bool #

(>=) :: Array i e -> Array i e -> Bool #

max :: Array i e -> Array i e -> Array i e #

min :: Array i e -> Array i e -> Array i e #

Array construction

array Source #

Arguments

:: (IArray a e, Ix i) 
=> (i, i)

bounds of the array: (lowest,highest)

-> [(i, e)]

list of associations

-> a i e 

Constructs an immutable array from a pair of bounds and a list of initial associations.

The bounds are specified as a pair of the lowest and highest bounds in the array respectively. For example, a one-origin vector of length 10 has bounds (1,10), and a one-origin 10 by 10 matrix has bounds ((1,1),(10,10)).

An association is a pair of the form (i,x), which defines the value of the array at index i to be x. The array is undefined if any index in the list is out of bounds. If any two associations in the list have the same index, the value at that index is implementation-dependent. (In GHC, the last value specified for that index is used. Other implementations will also do this for unboxed arrays, but Haskell 98 requires that for Array the value at such indices is bottom.)

Because the indices must be checked for these errors, array is strict in the bounds argument and in the indices of the association list. Whether array is strict or non-strict in the elements depends on the array type: Array is a non-strict array type, but all of the UArray arrays are strict. Thus in a non-strict array, recurrences such as the following are possible:

a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i \<- [2..100]])

Not every index within the bounds of the array need appear in the association list, but the values associated with indices that do not appear will be undefined.

If, in any dimension, the lower bound is greater than the upper bound, then the array is legal, but empty. Indexing an empty array always gives an array-bounds error, but bounds still yields the bounds with which the array was constructed.

listArray :: (IArray a e, Ix i) => (i, i) -> [e] -> a i e Source #

Constructs an immutable array from a list of initial elements. The list gives the elements of the array in ascending order beginning with the lowest index.

accumArray Source #

Arguments

:: (IArray a e, Ix i) 
=> (e -> e' -> e)

An accumulating function

-> e

A default element

-> (i, i)

The bounds of the array

-> [(i, e')]

List of associations

-> a i e

Returns: the array

Constructs an immutable array from a list of associations. Unlike array, the same index is allowed to occur multiple times in the list of associations; an accumulating function is used to combine the values of elements with the same index.

For example, given a list of values of some index type, hist produces a histogram of the number of occurrences of each index within a specified range:

hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a b
hist bnds is = accumArray (+) 0 bnds [(i, 1) | i\<-is, inRange bnds i]

genArray :: (IArray a e, Ix i) => (i, i) -> (i -> e) -> a i e Source #

Constructs an immutable array using a generator function.

Accessing arrays

(!) :: (IArray a e, Ix i) => a i e -> i -> e Source #

Returns the element of an immutable array at the specified index, or throws an exception if the index is out of bounds.

(!?) :: (IArray a e, Ix i) => a i e -> i -> Maybe e Source #

Returns Just the element of an immutable array at the specified index, or Nothing if the index is out of bounds.

bounds :: (IArray a e, Ix i) => a i e -> (i, i) Source #

Extracts the bounds of an immutable array

indices :: (IArray a e, Ix i) => a i e -> [i] Source #

Returns a list of all the valid indices in an array.

elems :: (IArray a e, Ix i) => a i e -> [e] Source #

Returns a list of all the elements of an array, in the same order as their indices.

assocs :: (IArray a e, Ix i) => a i e -> [(i, e)] Source #

Returns the contents of an array as a list of associations.

Incremental array updates

(//) :: (IArray a e, Ix i) => a i e -> [(i, e)] -> a i e Source #

Takes an array and a list of pairs and returns an array identical to the left argument except that it has been updated by the associations in the right argument. For example, if m is a 1-origin, n by n matrix, then m//[((i,i), 0) | i <- [1..n]] is the same matrix, except with the diagonal zeroed.

As with the array function, if any two associations in the list have the same index, the value at that index is implementation-dependent. (In GHC, the last value specified for that index is used. Other implementations will also do this for unboxed arrays, but Haskell 98 requires that for Array the value at such indices is bottom.)

For most array types, this operation is O(n) where n is the size of the array. However, the diffarray package provides an array type for which this operation has complexity linear in the number of updates.

accum :: (IArray a e, Ix i) => (e -> e' -> e) -> a i e -> [(i, e')] -> a i e Source #

accum f takes an array and an association list and accumulates pairs from the list into the array with the accumulating function f. Thus accumArray can be defined using accum:

accumArray f z b = accum f (array b [(i, z) | i \<- range b])

Derived arrays

amap :: (IArray a e', IArray a e, Ix i) => (e' -> e) -> a i e' -> a i e Source #

Returns a new array derived from the original array by applying a function to each of the elements.

ixmap :: (IArray a e, Ix i, Ix j) => (i, i) -> (i -> j) -> a j e -> a i e Source #

Returns a new array derived from the original array by applying a function to each of the indices.