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 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
- class IArray a e
- module Data.Ix
- data Array i e
- 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
- bounds :: (IArray a e, Ix i) => a i e -> (i, i)
- indices :: (IArray a e, 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)]
- (//) :: (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
Array classes
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
Instance details
Defined in Data.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
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Bool -> (i, i) Source #
numElements :: Ix i => UArray i Bool -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Bool)] -> UArray i Bool
unsafeAt :: Ix i => UArray i Bool -> Int -> Bool
unsafeReplace :: Ix i => UArray i Bool -> [(Int, Bool)] -> UArray i Bool
unsafeAccum :: Ix i => (Bool -> e' -> Bool) -> UArray i Bool -> [(Int, e')] -> UArray i Bool
unsafeAccumArray :: Ix i => (Bool -> e' -> Bool) -> Bool -> (i, i) -> [(Int, e')] -> UArray i Bool
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Char -> (i, i) Source #
numElements :: Ix i => UArray i Char -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Char)] -> UArray i Char
unsafeAt :: Ix i => UArray i Char -> Int -> Char
unsafeReplace :: Ix i => UArray i Char -> [(Int, Char)] -> UArray i Char
unsafeAccum :: Ix i => (Char -> e' -> Char) -> UArray i Char -> [(Int, e')] -> UArray i Char
unsafeAccumArray :: Ix i => (Char -> e' -> Char) -> Char -> (i, i) -> [(Int, e')] -> UArray i Char
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Double -> (i, i) Source #
numElements :: Ix i => UArray i Double -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Double)] -> UArray i Double
unsafeAt :: Ix i => UArray i Double -> Int -> Double
unsafeReplace :: Ix i => UArray i Double -> [(Int, Double)] -> UArray i Double
unsafeAccum :: Ix i => (Double -> e' -> Double) -> UArray i Double -> [(Int, e')] -> UArray i Double
unsafeAccumArray :: Ix i => (Double -> e' -> Double) -> Double -> (i, i) -> [(Int, e')] -> UArray i Double
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Float -> (i, i) Source #
numElements :: Ix i => UArray i Float -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Float)] -> UArray i Float
unsafeAt :: Ix i => UArray i Float -> Int -> Float
unsafeReplace :: Ix i => UArray i Float -> [(Int, Float)] -> UArray i Float
unsafeAccum :: Ix i => (Float -> e' -> Float) -> UArray i Float -> [(Int, e')] -> UArray i Float
unsafeAccumArray :: Ix i => (Float -> e' -> Float) -> Float -> (i, i) -> [(Int, e')] -> UArray i Float
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Int -> (i, i) Source #
numElements :: Ix i => UArray i Int -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Int)] -> UArray i Int
unsafeAt :: Ix i => UArray i Int -> Int -> Int
unsafeReplace :: Ix i => UArray i Int -> [(Int, Int)] -> UArray i Int
unsafeAccum :: Ix i => (Int -> e' -> Int) -> UArray i Int -> [(Int, e')] -> UArray i Int
unsafeAccumArray :: Ix i => (Int -> e' -> Int) -> Int -> (i, i) -> [(Int, e')] -> UArray i Int
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Int8 -> (i, i) Source #
numElements :: Ix i => UArray i Int8 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Int8)] -> UArray i Int8
unsafeAt :: Ix i => UArray i Int8 -> Int -> Int8
unsafeReplace :: Ix i => UArray i Int8 -> [(Int, Int8)] -> UArray i Int8
unsafeAccum :: Ix i => (Int8 -> e' -> Int8) -> UArray i Int8 -> [(Int, e')] -> UArray i Int8
unsafeAccumArray :: Ix i => (Int8 -> e' -> Int8) -> Int8 -> (i, i) -> [(Int, e')] -> UArray i Int8
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Int16 -> (i, i) Source #
numElements :: Ix i => UArray i Int16 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Int16)] -> UArray i Int16
unsafeAt :: Ix i => UArray i Int16 -> Int -> Int16
unsafeReplace :: Ix i => UArray i Int16 -> [(Int, Int16)] -> UArray i Int16
unsafeAccum :: Ix i => (Int16 -> e' -> Int16) -> UArray i Int16 -> [(Int, e')] -> UArray i Int16
unsafeAccumArray :: Ix i => (Int16 -> e' -> Int16) -> Int16 -> (i, i) -> [(Int, e')] -> UArray i Int16
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Int32 -> (i, i) Source #
numElements :: Ix i => UArray i Int32 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Int32)] -> UArray i Int32
unsafeAt :: Ix i => UArray i Int32 -> Int -> Int32
unsafeReplace :: Ix i => UArray i Int32 -> [(Int, Int32)] -> UArray i Int32
unsafeAccum :: Ix i => (Int32 -> e' -> Int32) -> UArray i Int32 -> [(Int, e')] -> UArray i Int32
unsafeAccumArray :: Ix i => (Int32 -> e' -> Int32) -> Int32 -> (i, i) -> [(Int, e')] -> UArray i Int32
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Int64 -> (i, i) Source #
numElements :: Ix i => UArray i Int64 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64
unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64
unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64
unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64
unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Word -> (i, i) Source #
numElements :: Ix i => UArray i Word -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Word)] -> UArray i Word
unsafeAt :: Ix i => UArray i Word -> Int -> Word
unsafeReplace :: Ix i => UArray i Word -> [(Int, Word)] -> UArray i Word
unsafeAccum :: Ix i => (Word -> e' -> Word) -> UArray i Word -> [(Int, e')] -> UArray i Word
unsafeAccumArray :: Ix i => (Word -> e' -> Word) -> Word -> (i, i) -> [(Int, e')] -> UArray i Word
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Word8 -> (i, i) Source #
numElements :: Ix i => UArray i Word8 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8
unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8
unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8
unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8
unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Word16 -> (i, i) Source #
numElements :: Ix i => UArray i Word16 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Word16)] -> UArray i Word16
unsafeAt :: Ix i => UArray i Word16 -> Int -> Word16
unsafeReplace :: Ix i => UArray i Word16 -> [(Int, Word16)] -> UArray i Word16
unsafeAccum :: Ix i => (Word16 -> e' -> Word16) -> UArray i Word16 -> [(Int, e')] -> UArray i Word16
unsafeAccumArray :: Ix i => (Word16 -> e' -> Word16) -> Word16 -> (i, i) -> [(Int, e')] -> UArray i Word16
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Word32 -> (i, i) Source #
numElements :: Ix i => UArray i Word32 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Word32)] -> UArray i Word32
unsafeAt :: Ix i => UArray i Word32 -> Int -> Word32
unsafeReplace :: Ix i => UArray i Word32 -> [(Int, Word32)] -> UArray i Word32
unsafeAccum :: Ix i => (Word32 -> e' -> Word32) -> UArray i Word32 -> [(Int, e')] -> UArray i Word32
unsafeAccumArray :: Ix i => (Word32 -> e' -> Word32) -> Word32 -> (i, i) -> [(Int, e')] -> UArray i Word32
Instance details
Defined in Data.Array.Base
Methods
bounds :: Ix i => UArray i Word64 -> (i, i) Source #
numElements :: Ix i => UArray i Word64 -> Int
unsafeArray :: Ix i => (i, i) -> [(Int, Word64)] -> UArray i Word64
unsafeAt :: Ix i => UArray i Word64 -> Int -> Word64
unsafeReplace :: Ix i => UArray i Word64 -> [(Int, Word64)] -> UArray i Word64
unsafeAccum :: Ix i => (Word64 -> e' -> Word64) -> UArray i Word64 -> [(Int, e')] -> UArray i Word64
unsafeAccumArray :: Ix i => (Word64 -> e' -> Word64) -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64
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
unsafeArray :: Ix i => (i, i) -> [(Int, StablePtr a)] -> UArray i (StablePtr a)
unsafeAt :: Ix i => UArray i (StablePtr a) -> Int -> StablePtr a
unsafeReplace :: Ix i => UArray i (StablePtr a) -> [(Int, StablePtr a)] -> UArray i (StablePtr a)
unsafeAccum :: Ix i => (StablePtr a -> e' -> StablePtr a) -> UArray i (StablePtr a) -> [(Int, e')] -> UArray i (StablePtr a)
unsafeAccumArray :: Ix i => (StablePtr a -> e' -> StablePtr a) -> StablePtr a -> (i, i) -> [(Int, e')] -> UArray i (StablePtr a)
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
unsafeArray :: Ix i => (i, i) -> [(Int, Ptr a)] -> UArray i (Ptr a)
unsafeAt :: Ix i => UArray i (Ptr a) -> Int -> Ptr a
unsafeReplace :: Ix i => UArray i (Ptr a) -> [(Int, Ptr a)] -> UArray i (Ptr a)
unsafeAccum :: Ix i => (Ptr a -> e' -> Ptr a) -> UArray i (Ptr a) -> [(Int, e')] -> UArray i (Ptr a)
unsafeAccumArray :: Ix i => (Ptr a -> e' -> Ptr a) -> Ptr a -> (i, i) -> [(Int, e')] -> UArray i (Ptr a)
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
unsafeArray :: Ix i => (i, i) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)
unsafeAt :: Ix i => UArray i (FunPtr a) -> Int -> FunPtr a
unsafeReplace :: Ix i => UArray i (FunPtr a) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)
unsafeAccum :: Ix i => (FunPtr a -> e' -> FunPtr a) -> UArray i (FunPtr a) -> [(Int, e')] -> UArray i (FunPtr a)
unsafeAccumArray :: Ix i => (FunPtr a -> e' -> FunPtr a) -> FunPtr a -> (i, i) -> [(Int, e')] -> UArray i (FunPtr a)
module Data.Ix
Immutable non-strict (boxed) arrays
The type of immutable non-strict (boxed) arrays
with indices in i
and elements in e
.
Instances
Instances details
Instance details
Defined in Data.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
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 #
elem :: Eq a => a -> Array i a -> Bool #
maximum :: Ord a => Array i a -> a #
minimum :: Ord a => Array i a -> a #
Since: base-2.1
Instance details
Defined in Data.Traversable
Array construction
Arguments
bounds of the array: (lowest,highest)
list of associations
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.
Arguments
An accumulating function
A default element
The bounds of the array
List of associations
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]
Accessing arrays
(!) :: (IArray a e, Ix i) => a i e -> i -> e Source #
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.
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])