- updateAll :: (MArray a e m, Ix i) => (e -> e) -> a i e -> m ()
- updateAllIx :: (MArray a e m, Ix i) => (i -> e -> e) -> a i e -> m ()
- updateAllM :: (MArray a e m, Ix i) => (e -> m e) -> a i e -> m ()
- updateAllIxM :: (MArray a e m, Ix i) => (i -> e -> m e) -> a i e -> m ()
- updateOn :: (MArray a e m, Ix i) => (e -> e) -> [i] -> a i e -> m ()
- updateOnIx :: (MArray a e m, Ix i) => (i -> e -> e) -> [i] -> a i e -> m ()
- updateOnM :: (MArray a e m, Ix i) => (e -> m e) -> [i] -> a i e -> m ()
- updateOnIxM :: (MArray a e m, Ix i) => (i -> e -> m e) -> [i] -> a i e -> m ()
- updateWithin :: (MArray a e m, Ix i) => (e -> e) -> (i, i) -> a i e -> m ()
- updateWithinIx :: (MArray a e m, Ix i, Show i) => (i -> e -> e) -> (i, i) -> a i e -> m ()
- updateWithinM :: (MArray a e m, Ix i) => (e -> m e) -> (i, i) -> a i e -> m ()
- updateWithinIxM :: (MArray a e m, Ix i, Show i) => (i -> e -> m e) -> (i, i) -> a i e -> m ()
- updateSlice :: (MArray a e m, Ix i) => (e -> e) -> (i, i) -> a i e -> m ()
- updateSliceM :: (MArray a e m, Ix i) => (e -> m e) -> (i, i) -> a i e -> m ()
Documentation
This module contains some primitive operations for working with
mutable Arrays
. They all try to avoid bounds checking as much
as possible, and should be quite fast.
Some functions throw IndexOutOfBounds
exceptions. If an exception
is thrown, the array will be left untouched, meaning it may be ok to
catch the exception, and continue using the array.
Each function has four varieties: a simple version which uses a pure function ('e -> e') to update each element, a version which also passes the element's index to the pure function ('i -> e -> e'), and two monadic versions of the previous two ('e -> m e', 'i -> e -> m e'), which are useful for reading other elements of the array, or filling the array with values from an external source.
This library relies on some of the primitives in GHC.Arr, so is probably not portable.
Updating all elements
updateAll mutates every element in an array while avoiding all bounds checks. Think of it as a mutable version of map. O(size of arr)
>>>
arr <- newArray (1,10) 0 :: IO (IOArray Int Int)
-- Produces a 1 based array with 10 elements all set to 0.>>>
updateAll arr (+ 10)
-- Updates all elements to 10
updateAllIx :: (MArray a e m, Ix i) => (i -> e -> e) -> a i e -> m ()Source
The same as updateAll, but also providing the index to the mapping function. O(size of arr)
Monadic versions
updateAllM :: (MArray a e m, Ix i) => (e -> m e) -> a i e -> m ()Source
The same as updateAll but taking a monadic function. O(size of arr)
updateAllIxM :: (MArray a e m, Ix i) => (i -> e -> m e) -> a i e -> m ()Source
The same updateAllIx but taking a monadic function. O(size of arr)
Updating certain elements
:: (MArray a e m, Ix i) | |
=> (e -> e) | Update function |
-> [i] | A list of indicies to update |
-> a i e | The array |
-> m () |
Takes a mapping function, and a list of indicies to mutate.
Throws an IndexOutOfBounds
exception if any of the indicies are
out of bounds. In this case the array will be left unmutated.
O(length xs)
updateOnIx :: (MArray a e m, Ix i) => (i -> e -> e) -> [i] -> a i e -> m ()Source
Monadic versions
updateOnIxM :: (MArray a e m, Ix i) => (i -> e -> m e) -> [i] -> a i e -> m ()Source
Updating within a bounded area
:: (MArray a e m, Ix i) | |
=> (e -> e) | Update function |
-> (i, i) | The bounds within which to apply f. |
-> a i e | The array |
-> m () |
Takes an update function f
and a tuple of indicies '(start, finish)',
and applies the function to all elements returned by 'range (start, finish)'.
If this is a 2D array, then the area updated will be the box bounded by these elements, and the rectangular prism area for a 3D array etc.
Throws an IndexOutOfBounds
exception if either of the indicies are out of bounds.
Monadic versions
updateWithinM :: (MArray a e m, Ix i) => (e -> m e) -> (i, i) -> a i e -> m ()Source
Updating slices
Note the difference between these functions and updateWithin. These functions will update every element whose index holds this property:
f x = index (start,end) start <= ix && ix <= index (start,end) end where ix = index (start, end) x
For example:
>>>
arr <- newArray ((1,1),(5,5)) 0 :: IO (IOArray Int Int)
-- Produces a 2D array with 25 elements all set to 0.>>>
updateSlice ((2,4),(3,5)) (+ 10) arr
-- Updates elements at indexes: -- [(2,4),(2,5), -- (3,1),(3,2),(3,3),(3,4),(3,5)] -- to 10
*Ix versions are not included, because there's no easy way to map from an Int to an element in a particular bounds.
All of these functions may throw IndexOutOfBounds
exceptions.
:: (MArray a e m, Ix i) | |
=> (e -> e) | Update function |
-> (i, i) | The start and end of the region to update |
-> a i e | The array |
-> m () |
updateSlice mutates every element in an array between a start index and an end index. O(size of arr)
>>>
arr <- newArray (1,10) 0 :: IO (IOArray Int Int)
-- Produces a 1 based array with 10 elements all set to 0.>>>
updateSlice arr (2,4) (+ 10)
-- Updates elements at indexes 2, 3 and 4 to 10
Monadic versions
updateSliceM :: (MArray a e m, Ix i) => (e -> m e) -> (i, i) -> a i e -> m ()Source