base-4.1.0.0: Basic librariesSource codeContentsIndex
GHC.Arr
Portabilitynon-portable (GHC extensions)
Stabilityinternal
Maintainercvs-ghc@haskell.org
Description
GHC's array implementation.
Synopsis
class Ord a => Ix a where
range :: (a, a) -> [a]
index :: (a, a) -> a -> Int
unsafeIndex :: (a, a) -> a -> Int
inRange :: (a, a) -> a -> Bool
rangeSize :: (a, a) -> Int
unsafeRangeSize :: (a, a) -> Int
indexError :: Show a => (a, a) -> a -> String -> b
type IPr = (Int, Int)
data Ix i => Array i e = Array !i !i !Int (Array# e)
data STArray s i e = STArray !i !i !Int (MutableArray# s e)
arrEleBottom :: a
array :: Ix i => (i, i) -> [(i, e)] -> Array i e
unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> Array i e
unsafeArray' :: Ix i => (i, i) -> Int -> [(Int, e)] -> Array i e
fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a
done :: Ix i => i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)
listArray :: Ix i => (i, i) -> [e] -> Array i e
(!) :: Ix i => Array i e -> i -> e
safeRangeSize :: Ix i => (i, i) -> Int
safeIndex :: Ix i => (i, i) -> Int -> i -> Int
unsafeAt :: Ix i => Array i e -> Int -> e
bounds :: Ix i => Array i e -> (i, i)
numElements :: Ix i => Array i e -> Int
indices :: Ix i => Array i e -> [i]
elems :: Ix i => Array i e -> [e]
assocs :: Ix i => Array i e -> [(i, e)]
accumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(i, a)] -> Array i e
unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(Int, a)] -> Array i e
unsafeAccumArray' :: Ix i => (e -> a -> e) -> e -> (i, i) -> Int -> [(Int, a)] -> Array i e
adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b
(//) :: Ix i => Array i e -> [(i, e)] -> Array i e
unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i e
accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e
unsafeAccum :: Ix i => (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e
amap :: Ix i => (a -> b) -> Array i a -> Array i b
ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i e
eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> Bool
cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> Ordering
cmpIntArray :: Ord e => Array Int e -> Array Int e -> Ordering
newSTArray :: Ix i => (i, i) -> e -> ST s (STArray s i e)
boundsSTArray :: STArray s i e -> (i, i)
numElementsSTArray :: STArray s i e -> Int
readSTArray :: Ix i => STArray s i e -> i -> ST s e
unsafeReadSTArray :: Ix i => STArray s i e -> Int -> ST s e
writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s ()
unsafeWriteSTArray :: Ix i => STArray s i e -> Int -> e -> ST s ()
freezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
unsafeFreezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
thawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
unsafeThawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
Documentation
class Ord a => Ix a whereSource

The Ix class is used to map a contiguous subrange of values in a type onto integers. It is used primarily for array indexing (see the array package).

The first argument (l,u) of each of these operations is a pair specifying the lower and upper bounds of a contiguous subrange of values.

An implementation is entitled to assume the following laws about these operations:

Minimal complete instance: range, index and inRange.

Methods
range :: (a, a) -> [a]Source
The list of values in the subrange defined by a bounding pair.
index :: (a, a) -> a -> IntSource
The position of a subscript in the subrange.
unsafeIndex :: (a, a) -> a -> IntSource
Like index, but without checking that the value is in range.
inRange :: (a, a) -> a -> BoolSource
Returns True the given subscript lies in the range defined the bounding pair.
rangeSize :: (a, a) -> IntSource
The size of the subrange defined by a bounding pair.
unsafeRangeSize :: (a, a) -> IntSource
like rangeSize, but without checking that the upper bound is in range.
show/hide Instances
Ix Bool
Ix Char
Ix Int
Ix Int8
Ix Int16
Ix Int32
Ix Int64
Ix Integer
Ix Ordering
Ix Word
Ix Word8
Ix Word16
Ix Word32
Ix Word64
Ix ()
Ix IOMode
Ix GeneralCategory
Ix SeekMode
(Ix a, Ix b) => Ix ((,) a b)
(Ix a1, Ix a2, Ix a3) => Ix ((,,) a1 a2 a3)
(Ix a1, Ix a2, Ix a3, Ix a4) => Ix ((,,,) a1 a2 a3 a4)
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix ((,,,,) a1 a2 a3 a4 a5)
indexError :: Show a => (a, a) -> a -> String -> bSource
type IPr = (Int, Int)Source
data Ix i => Array i e Source
The type of immutable non-strict (boxed) arrays with indices in i and elements in e. The Int is the number of elements in the Array.
Constructors
Array !i !i !Int (Array# e)
show/hide Instances
Typeable2 Array
Ix i => Functor (Array i)
Ix i => Foldable (Array i)
Ix i => Traversable (Array i)
(Ix i, Eq e) => Eq (Array i e)
(Typeable a, Data b, Ix a) => Data (Array a b)
(Ix i, Ord e) => Ord (Array i e)
(Ix a, Read a, Read b) => Read (Array a b)
(Ix a, Show a, Show b) => Show (Array a b)
data STArray s i e Source

Mutable, boxed, non-strict arrays in the ST monad. The type arguments are as follows:

  • s: the state variable argument for the ST type
  • i: the index type of the array (should be an instance of Ix)
  • e: the element type of the array.
Constructors
STArray !i !i !Int (MutableArray# s e)
show/hide Instances
arrEleBottom :: aSource
arraySource
:: Ix i
=> (i, i)a pair of bounds, each of the index type of the array. These bounds are the lowest and highest indices in the array, in that order. 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))'.
-> [(i, e)]a list of associations of the form (index, value). Typically, this list will be expressed as a comprehension. An association '(i, x)' defines the value of the array at index i to be x.
-> Array i e

Construct an array with the specified bounds and containing values for given indices within these bounds.

The array is undefined (i.e. bottom) if any index in the list is out of bounds. The Haskell 98 Report further specifies that if any two associations in the list have the same index, the value at that index is undefined (i.e. bottom). However in GHC's implementation, the value at such an index is the value part of the last association with that index in the list.

Because the indices must be checked for these errors, array is strict in the bounds argument and in the indices of the association list, but nonstrict in the values. Thus, 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 (i.e. bottom).

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.

unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> Array i eSource
unsafeArray' :: Ix i => (i, i) -> Int -> [(Int, e)] -> Array i eSource
fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s aSource
done :: Ix i => i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)Source
listArray :: Ix i => (i, i) -> [e] -> Array i eSource
Construct an array from a pair of bounds and a list of values in index order.
(!) :: Ix i => Array i e -> i -> eSource
The value at the given index in an array.
safeRangeSize :: Ix i => (i, i) -> IntSource
safeIndex :: Ix i => (i, i) -> Int -> i -> IntSource
unsafeAt :: Ix i => Array i e -> Int -> eSource
bounds :: Ix i => Array i e -> (i, i)Source
The bounds with which an array was constructed.
numElements :: Ix i => Array i e -> IntSource
The number of elements in the array.
indices :: Ix i => Array i e -> [i]Source
The list of indices of an array in ascending order.
elems :: Ix i => Array i e -> [e]Source
The list of elements of an array in index order.
assocs :: Ix i => Array i e -> [(i, e)]Source
The list of associations of an array in index order.
accumArraySource
:: Ix i
=> e -> a -> eaccumulating function
-> einitial value
-> (i, i)bounds of the array
-> [(i, a)]association list
-> Array i e

The accumArray deals with repeated indices in the association list using an accumulating function which combines the values of associations 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]

If the accumulating function is strict, then accumArray is strict in the values, as well as the indices, in the association list. Thus, unlike ordinary arrays built with array, accumulated arrays should not in general be recursive.

unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(Int, a)] -> Array i eSource
unsafeAccumArray' :: Ix i => (e -> a -> e) -> e -> (i, i) -> Int -> [(Int, a)] -> Array i eSource
adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s bSource
(//) :: Ix i => Array i e -> [(i, e)] -> Array i eSource

Constructs an array identical to the first 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.

Repeated indices in the association list are handled as for array: Haskell 98 specifies that the resulting array is undefined (i.e. bottom), but GHC's implementation uses the last association for each index.

unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i eSource
accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i eSource

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])
unsafeAccum :: Ix i => (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i eSource
amap :: Ix i => (a -> b) -> Array i a -> Array i bSource
ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i eSource

ixmap allows for transformations on array indices. It may be thought of as providing function composition on the right with the mapping that the original array embodies.

A similar transformation of array values may be achieved using fmap from the Array instance of the Functor class.

eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> BoolSource
cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> OrderingSource
cmpIntArray :: Ord e => Array Int e -> Array Int e -> OrderingSource
newSTArray :: Ix i => (i, i) -> e -> ST s (STArray s i e)Source
boundsSTArray :: STArray s i e -> (i, i)Source
numElementsSTArray :: STArray s i e -> IntSource
readSTArray :: Ix i => STArray s i e -> i -> ST s eSource
unsafeReadSTArray :: Ix i => STArray s i e -> Int -> ST s eSource
writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s ()Source
unsafeWriteSTArray :: Ix i => STArray s i e -> Int -> e -> ST s ()Source
freezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)Source
unsafeFreezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)Source
thawSTArray :: Ix i => Array i e -> ST s (STArray s i e)Source
unsafeThawSTArray :: Ix i => Array i e -> ST s (STArray s i e)Source
Produced by Haddock version 2.4.2