Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Array i e
- array :: Ix i => (i, i) -> [(i, e)] -> Array i e
- bounds :: Array i e -> (i, i)
- indices :: Ix i => Array i e -> [i]
- assocs :: Ix i => Array i e -> [(i, e)]
- (//) :: Ix i => Array i e -> [(i, e)] -> Array i e
- accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e
- ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i e
Documentation
The type of immutable non-strict (boxed) arrays
with indices in i
and elements in e
.
Instances
NFData2 Array | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Functor (Array i) | Since: base-2.1 |
Foldable (Array i) | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Array i m -> 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 # | |
Ix i => Traversable (Array i) | Since: base-2.1 |
NFData a => NFData1 (Array a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
(Ix i, Eq e) => Eq (Array i e) | Since: base-2.1 |
(Data a, Data b, Ix a) => Data (Array a b) | Since: base-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) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a b) # toConstr :: Array a b -> Constr # dataTypeOf :: Array a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Array a b -> Array a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Array a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) # | |
(Ix i, Ord e) => Ord (Array i e) | Since: base-2.1 |
Defined in GHC.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 |
(NFData a, NFData b) => NFData (Array a b) | |
Defined in Control.DeepSeq | |
Ix i => Ixed (Array i e) | arr |
Defined in Control.Lens.At | |
(Ix i, i ~ j) => Each (Array i a) (Array j b) a b |
|
type Index (Array i e) | |
Defined in Control.Lens.At | |
type IxValue (Array i e) | |
Defined in Control.Lens.At |
:: 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 |
-> 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.
(//) :: Ix i => Array i e -> [(i, e)] -> Array i e infixl 9 #
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 #
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])