Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | non-portable (uses Data.Array.Base) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Data.Array.IArray
Description
Immutable arrays, with an overloaded interface. For array types which can be used with this interface, see theArray
type exported by this module and theData.Array.Unboxed module. Other packages, such as diffarray, also provide arrays using this interface.
Class of immutable array types.
An array type has the form(a i e)
wherea
is the array typeconstructor (kind* -> * -> *
),i
is the index type (a member ofthe classIx
), ande
is the element type. TheIArray
class isparameterised over botha
ande
, so that instances specialised tocertain element types can be defined.
Minimal complete definition
bounds, numElements, unsafeArray, unsafeAt
moduleData.Ix
The type of immutable non-strict (boxed) arrays with indices ini
and elements ine
.
IArrayArray eSource# | |
Instance detailsDefined inData.Array.Base Methods bounds ::Ix i =>Array i e -> (i, i)Source# numElements ::Ix i =>Array i e ->Int unsafeArray ::Ix i => (i, i) -> [(Int, e)] ->Array i e unsafeAt ::Ix i =>Array i e ->Int -> e unsafeReplace ::Ix i =>Array i e -> [(Int, e)] ->Array i e unsafeAccum ::Ix i => (e -> e' -> e) ->Array i e -> [(Int, e')] ->Array i e unsafeAccumArray ::Ix i => (e -> e' -> e) -> e -> (i, i) -> [(Int, e')] ->Array i e | |
Functor (Array i) | Since: base-2.1 |
Foldable (Array i) | Since: base-4.8.0.0 |
Instance detailsDefined inData.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# elem ::Eq a => a ->Array i a ->Bool# maximum ::Ord a =>Array i a -> a# | |
Ix i =>Traversable (Array i) | Since: base-2.1 |
(Ix i,Eq e) =>Eq (Array i e) | Since: base-2.1 |
(Ix i,Ord e) =>Ord (Array i e) | Since: base-2.1 |
Instance detailsDefined inGHC.Arr | |
(Ix a,Read a,Read b) =>Read (Array a b) | Since: base-2.1 |
(Ix a,Show a,Show b) =>Show (Array a b) | Since: base-2.1 |
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 ofinitial associations.
The bounds are specified as a pair of the lowest and highest bounds inthe array respectively. For example, a one-origin vector of length 10has 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 ofthe array at indexi
to bex
. The array is undefined if any indexin the list is out of bounds. If any two associations in the list havethe 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 Haskell98 requires that forArray
the value at such indices is bottom.)
Because the indices must be checked for these errors,array
isstrict in the bounds argument and in the indices of the associationlist. Whetherarray
is strict or non-strict in the elements dependson the array type:Array
is a non-strict array type, butall of theUArray
arrays are strict. Thus in anon-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 theassociation list, but the values associated with indices that do notappear 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 alwaysgives an array-bounds error, butbounds
still yields the bounds withwhich the array was constructed.
listArray :: (IArray a e,Ix i) => (i, i) -> [e] -> a i eSource#
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.
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. Unlikearray
, the same index is allowed to occur multiple times in the listof associations; anaccumulating function is used to combine thevalues of elements with the same index.
For example, given a list of values of some index type, hist producesa histogram of the number of occurrences of each index within aspecified range:
hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a bhist bnds is = accumArray (+) 0 bnds [(i, 1) | i\<-is, inRange bnds i]
(!) :: (IArray a e,Ix i) => a i e -> i -> eSource#
Returns the element of an immutable array at the specified index.
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.
(//) :: (IArray a e,Ix i) => a i e -> [(i, e)] -> a i eSource#
Takes an array and a list of pairs and returns an array identical tothe left argument except that it has been updated by the associationsin the right argument. For example, if m is a 1-origin, n by n matrix,thenm//[((i,i), 0) | i <- [1..n]]
is the same matrix, except withthe diagonal zeroed.
As with thearray
function, if any two associations in the list havethe 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 Haskell98 requires that forArray
the value at such indices is bottom.)
For most array types, this operation is O(n) wheren is the sizeof the array. However, the diffarray package provides an array typefor 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 eSource#
accum f
takes an array and an association list and accumulates pairsfrom the list into the array with the accumulating functionf
. ThusaccumArray
can be defined usingaccum
:
accumArray f z b = accum f (array b [(i, z) | i \<- range b])
Produced byHaddock version 2.23.0