Copyright | (c) The University of Glasgow 1994-2000 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
GHC's array implementation.
Synopsis
- class Ord a => Ix a where
- data 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
- listArray :: Ix i => (i, i) -> [e] -> Array i e
- (!) :: Ix i => Array i e -> i -> e
- safeRangeSize :: Ix i => (i, i) -> Int
- negRange :: Int
- safeIndex :: Ix i => (i, i) -> Int -> i -> Int
- badSafeIndex :: Int -> Int -> Int
- bounds :: Array i e -> (i, i)
- numElements :: Array i e -> Int
- numElementsSTArray :: STArray s i e -> Int
- indices :: Ix i => Array i e -> [i]
- elems :: 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
- 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
- accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e
- amap :: (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)
- readSTArray :: Ix i => STArray s i e -> i -> ST s e
- writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s ()
- freezeSTArray :: STArray s i e -> ST s (Array i e)
- thawSTArray :: Array i e -> ST s (STArray s i e)
- foldlElems :: (b -> a -> b) -> b -> Array i a -> b
- foldlElems' :: (b -> a -> b) -> b -> Array i a -> b
- foldl1Elems :: (a -> a -> a) -> Array i a -> a
- foldrElems :: (a -> b -> b) -> b -> Array i a -> b
- foldrElems' :: (a -> b -> b) -> b -> Array i a -> b
- foldr1Elems :: (a -> a -> a) -> Array i a -> a
- fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a
- done :: i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)
- unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> Array i e
- unsafeArray' :: (i, i) -> Int -> [(Int, e)] -> Array i e
- lessSafeIndex :: Ix i => (i, i) -> Int -> i -> Int
- unsafeAt :: Array i e -> Int -> e
- unsafeReplace :: Array i e -> [(Int, e)] -> Array i e
- unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(Int, a)] -> Array i e
- unsafeAccumArray' :: (e -> a -> e) -> e -> (i, i) -> Int -> [(Int, a)] -> Array i e
- unsafeAccum :: (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e
- unsafeReadSTArray :: STArray s i e -> Int -> ST s e
- unsafeWriteSTArray :: STArray s i e -> Int -> e -> ST s ()
- unsafeFreezeSTArray :: STArray s i e -> ST s (Array i e)
- unsafeThawSTArray :: Array i e -> ST s (STArray s i e)
Documentation
class Ord a => Ix a where Source #
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:
range, (index | unsafeIndex), inRange
range :: (a, a) -> [a] Source #
The list of values in the subrange defined by a bounding pair.
index :: (a, a) -> a -> Int Source #
The position of a subscript in the subrange.
unsafeIndex :: (a, a) -> a -> Int Source #
Like index
, but without checking that the value is in range.
inRange :: (a, a) -> a -> Bool Source #
Returns True
the given subscript lies in the range defined
the bounding pair.
rangeSize :: (a, a) -> Int Source #
The size of the subrange defined by a bounding pair.
unsafeRangeSize :: (a, a) -> Int Source #
like rangeSize
, but without checking that the upper bound is
in range.
Instances
The type of immutable non-strict (boxed) arrays
with indices in i
and elements in e
.
Instances
Functor (Array i) Source # | Since: 2.1 |
Foldable (Array i) Source # | Since: 4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Array i m -> m Source # foldMap :: Monoid m => (a -> m) -> Array i a -> m Source # foldMap' :: Monoid m => (a -> m) -> Array i a -> m Source # foldr :: (a -> b -> b) -> b -> Array i a -> b Source # foldr' :: (a -> b -> b) -> b -> Array i a -> b Source # foldl :: (b -> a -> b) -> b -> Array i a -> b Source # foldl' :: (b -> a -> b) -> b -> Array i a -> b Source # foldr1 :: (a -> a -> a) -> Array i a -> a Source # foldl1 :: (a -> a -> a) -> Array i a -> a Source # toList :: Array i a -> [a] Source # null :: Array i a -> Bool Source # length :: Array i a -> Int Source # elem :: Eq a => a -> Array i a -> Bool Source # maximum :: Ord a => Array i a -> a Source # minimum :: Ord a => Array i a -> a Source # | |
Ix i => Traversable (Array i) Source # | Since: 2.1 |
Defined in Data.Traversable | |
(Ix i, Eq e) => Eq (Array i e) Source # | Since: 2.1 |
(Data a, Data b, Ix a) => Data (Array a b) Source # | Since: 4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Array a b -> c (Array a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a b) Source # toConstr :: Array a b -> Constr Source # dataTypeOf :: Array a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Array a b -> Array a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Array a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) Source # | |
(Ix i, Ord e) => Ord (Array i e) Source # | Since: 2.1 |
Defined in GHC.Arr | |
(Ix a, Read a, Read b) => Read (Array a b) Source # | Since: 2.1 |
(Ix a, Show a, Show b) => Show (Array a b) Source # | Since: 2.1 |
Mutable, boxed, non-strict arrays in the ST
monad. The type
arguments are as follows:
STArray !i !i !Int (MutableArray# s e) |
arrEleBottom :: a Source #
:: 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
|
-> [(i, e)] | a list of associations of the form
(index, value). Typically, this list will
be expressed as a comprehension. An
association |
-> 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 2010 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 non-strict 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.
listArray :: Ix i => (i, i) -> [e] -> Array i e Source #
Construct an array from a pair of bounds and a list of values in index order.
safeRangeSize :: Ix i => (i, i) -> Int Source #
numElements :: Array i e -> Int Source #
The number of elements in the array.
numElementsSTArray :: STArray s i e -> Int Source #
assocs :: Ix i => Array i e -> [(i, e)] Source #
The list of associations of an array in index order.
:: Ix i | |
=> (e -> a -> e) | accumulating function |
-> e | initial value |
-> (i, i) | bounds of the array |
-> [(i, a)] | association list |
-> Array i e |
The accumArray
function 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]
accumArray
is strict in each result of applying the accumulating
function, although it is lazy in the initial value. Thus, unlike
arrays built with array
, accumulated arrays should not in general
be recursive.
(//) :: Ix i => Array i e -> [(i, e)] -> Array i e infixl 9 Source #
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 2010 specifies that the resulting array is undefined (i.e. bottom),
but GHC's implementation uses the last association for each index.
accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e Source #
takes an array and an association list and accumulates
pairs from the list into the array with the accumulating function accum
ff
.
Thus accumArray
can be defined using accum
:
accumArray f z b = accum f (array b [(i, z) | i <- range b])
accum
is strict in all the results of applying the accumulation.
However, it is lazy in the initial values of the array.
boundsSTArray :: STArray s i e -> (i, i) Source #
foldlElems :: (b -> a -> b) -> b -> Array i a -> b Source #
A left fold over the elements
foldlElems' :: (b -> a -> b) -> b -> Array i a -> b Source #
A strict left fold over the elements
foldl1Elems :: (a -> a -> a) -> Array i a -> a Source #
A left fold over the elements with no starting value
foldrElems :: (a -> b -> b) -> b -> Array i a -> b Source #
A right fold over the elements
foldrElems' :: (a -> b -> b) -> b -> Array i a -> b Source #
A strict right fold over the elements
foldr1Elems :: (a -> a -> a) -> Array i a -> a Source #
A right fold over the elements with no starting value