Haskell Hierarchical Libraries (base package)ContentsIndex
Data.Array.IArray
Portability non-portable
Stability experimental
Maintainer libraries@haskell.org
Contents
Class of immutable array types
Class of array types with immutable bounds
Ordinary boxed/lazy arrays
The Ix class and operations
Array construction
Indexing arrays
Incremental updates
Derived Arrays
Deconstructing arrays
Description
Immutable arrays, with an overloaded interface. For array types which can be used with this interface, see Data.Array, Data.Array.Unboxed, and Data.Array.Diff.
Synopsis
class HasBounds a => IArray a e
class HasBounds a
data Array i e
module Data.Ix
array :: (IArray a e, Ix i) => (i, i) -> [(i, e)] -> a i e
listArray :: (IArray a e, Ix i) => (i, i) -> [e] -> a i e
accumArray :: (IArray a e, Ix i) => (e -> e' -> e) -> e -> (i, i) -> [(i, e')] -> a i e
(!) :: (IArray a e, Ix i) => a i e -> i -> e
(//) :: (IArray a e, Ix i) => a i e -> [(i, e)] -> a i e
accum :: (IArray a e, Ix i) => (e -> e' -> e) -> a i e -> [(i, e')] -> a i e
amap :: (IArray a e', IArray a e, Ix i) => (e' -> e) -> a i e' -> a i e
ixmap :: (IArray a e, Ix i, Ix j) => (i, i) -> (i -> j) -> a j e -> a i e
bounds :: (HasBounds a, Ix i) => a i e -> (i, i)
indices :: (HasBounds a, Ix i) => a i e -> [i]
elems :: (IArray a e, Ix i) => a i e -> [e]
assocs :: (IArray a e, Ix i) => a i e -> [(i, e)]
Class of immutable array types
class HasBounds a => IArray a e

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.

Instances
IArray Array e
IArray UArray Bool
IArray UArray Char
IArray UArray Int
IArray UArray Word
IArray UArray (Ptr a)
IArray UArray (FunPtr a)
IArray UArray Float
IArray UArray Double
IArray UArray (StablePtr a)
IArray UArray Int8
IArray UArray Int16
IArray UArray Int32
IArray UArray Int64
IArray UArray Word8
IArray UArray Word16
IArray UArray Word32
IArray UArray Word64
IArray (IOToDiffArray IOArray) e
IArray (IOToDiffArray IOUArray) Char
IArray (IOToDiffArray IOUArray) Int
IArray (IOToDiffArray IOUArray) Word
IArray (IOToDiffArray IOUArray) (Ptr a)
IArray (IOToDiffArray IOUArray) (FunPtr a)
IArray (IOToDiffArray IOUArray) Float
IArray (IOToDiffArray IOUArray) Double
IArray (IOToDiffArray IOUArray) (StablePtr a)
IArray (IOToDiffArray IOUArray) Int8
IArray (IOToDiffArray IOUArray) Int16
IArray (IOToDiffArray IOUArray) Int32
IArray (IOToDiffArray IOUArray) Int64
IArray (IOToDiffArray IOUArray) Word8
IArray (IOToDiffArray IOUArray) Word16
IArray (IOToDiffArray IOUArray) Word32
IArray (IOToDiffArray IOUArray) Word64
Class of array types with immutable bounds
class HasBounds a
Class of array types with bounds
Instances
HasBounds Array
HasBounds UArray
HasBounds (STArray s)
HasBounds (STUArray s)
HasBounds a => HasBounds (IOToDiffArray a)
HasBounds IOArray
HasBounds IOUArray
HasBounds StorableArray
Ordinary boxed/lazy arrays
data Array i e
Instances
(Typeable a, Typeable b) => Typeable (Array a b)
HasBounds Array
IArray Array e
Ix i => Functor (Array i)
(Ix i, Eq e) => Eq (Array i e)
(Ix i, Ord e) => Ord (Array i e)
(Ix a, Show a, Show b) => Show (Array a b)
(Ix a, Read a, Read b) => Read (Array a b)
The Ix class and operations
module Data.Ix
Array construction
array
:: (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 undefined.

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
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
:: (IArray a e, Ix i)
=> (e -> e' -> e)An accumulating function
-> eA default element
-> (i, i)The bounds of the array
-> [(i, e')]List of associations
-> a i eReturns: 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]
Indexing arrays
(!) :: (IArray a e, Ix i) => a i e -> i -> e
Returns the element of an immutable array at the specified index.
Incremental updates
(//) :: (IArray a e, Ix i) => a i e -> [(i, e)] -> a i e

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. (As with the array function, the indices in the association list must be unique for the updated elements to be defined.) 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.

For most array types, this operation is O(n) where n is the size of the array. However, the DiffArray type provides this operation with complexity linear in the number of updates.

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

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
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
Returns a new array derived from the original array by applying a function to each of the indices.
Deconstructing arrays
bounds :: (HasBounds a, Ix i) => a i e -> (i, i)
Extracts the bounds of an array
indices :: (HasBounds a, Ix i) => a i e -> [i]
Returns a list of all the valid indices in an array.
elems :: (IArray a e, Ix i) => a i e -> [e]
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)]
Returns the contents of an array as a list of associations.
Produced by Haddock version 0.6