-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Mutable and immutable arrays -- -- This package defines the classes IArray of immutable arrays -- and MArray of arrays mutable within appropriate monads, as -- well as some instances of these classes. @package array @version 0.3.0.2 -- | An overloaded interface to mutable arrays. For array types which can -- be used with this interface, see Data.Array.IO, -- Data.Array.ST, and Data.Array.Storable. module Data.Array.MArray -- | Class of mutable 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 MArray class is parameterised over both a and -- e (so that instances specialised to certain element types can -- be defined, in the same way as for IArray), and also over the -- type of the monad, m, in which the mutable array will be -- manipulated. class Monad m => MArray a e m getBounds :: (MArray a e m, Ix i) => a i e -> m (i, i) newArray :: (MArray a e m, Ix i) => (i, i) -> e -> m (a i e) newArray_ :: (MArray a e m, Ix i) => (i, i) -> m (a i e) -- | Constructs a mutable array from a list of initial elements. The list -- gives the elements of the array in ascending order beginning with the -- lowest index. newListArray :: (MArray a e m, Ix i) => (i, i) -> [e] -> m (a i e) -- | Read an element from a mutable array readArray :: (MArray a e m, Ix i) => a i e -> i -> m e -- | Write an element in a mutable array writeArray :: (MArray a e m, Ix i) => a i e -> i -> e -> m () -- | Constructs a new array derived from the original array by applying a -- function to each of the elements. mapArray :: (MArray a e' m, MArray a e m, Ix i) => (e' -> e) -> a i e' -> m (a i e) -- | Constructs a new array derived from the original array by applying a -- function to each of the indices. mapIndices :: (MArray a e m, Ix i, Ix j) => (i, i) -> (i -> j) -> a j e -> m (a i e) -- | Return a list of all the elements of a mutable array getElems :: (MArray a e m, Ix i) => a i e -> m [e] -- | Return a list of all the associations of a mutable array, in index -- order. getAssocs :: (MArray a e m, Ix i) => a i e -> m [(i, e)] -- | Converts a mutable array (any instance of MArray) to an -- immutable array (any instance of IArray) by taking a complete -- copy of it. freeze :: (Ix i, MArray a e m, IArray b e) => a i e -> m (b i e) -- | Converts an mutable array into an immutable array. The implementation -- may either simply cast the array from one type to the other without -- copying the array, or it may take a full copy of the array. -- -- Note that because the array is possibly not copied, any subsequent -- modifications made to the mutable version of the array may be shared -- with the immutable version. It is safe to use, therefore, if the -- mutable version is never modified after the freeze operation. -- -- The non-copying implementation is supported between certain pairs of -- array types only; one constraint is that the array types must have -- identical representations. In GHC, The following pairs of array types -- have a non-copying O(1) implementation of unsafeFreeze. Because -- the optimised versions are enabled by specialisations, you will need -- to compile with optimisation (-O) to get them. -- -- unsafeFreeze :: (Ix i, MArray a e m, IArray b e) => a i e -> m (b i e) -- | Converts an immutable array (any instance of IArray) into a -- mutable array (any instance of MArray) by taking a complete -- copy of it. thaw :: (Ix i, IArray a e, MArray b e m) => a i e -> m (b i e) -- | Converts an immutable array into a mutable array. The implementation -- may either simply cast the array from one type to the other without -- copying the array, or it may take a full copy of the array. -- -- Note that because the array is possibly not copied, any subsequent -- modifications made to the mutable version of the array may be shared -- with the immutable version. It is only safe to use, therefore, if the -- immutable array is never referenced again in this thread, and there is -- no possibility that it can be also referenced in another thread. If -- you use an unsafeThawwriteunsafeFreeze sequence in a -- multi-threaded setting, then you must ensure that this sequence is -- atomic with respect to other threads, or a garbage collector crash may -- result (because the write may be writing to a frozen array). -- -- The non-copying implementation is supported between certain pairs of -- array types only; one constraint is that the array types must have -- identical representations. In GHC, The following pairs of array types -- have a non-copying O(1) implementation of unsafeThaw. Because -- the optimised versions are enabled by specialisations, you will need -- to compile with optimisation (-O) to get them. -- -- unsafeThaw :: (Ix i, IArray a e, MArray b e m) => a i e -> m (b i e) -- | Mutable boxed and unboxed arrays in the IO monad. module Data.Array.IO -- | An IOArray is a mutable, boxed, non-strict array in the -- IO monad. The type arguments are as follows: -- -- data IOArray i e :: * -> * -> * -- | Mutable, unboxed, strict arrays in the IO monad. The type -- arguments are as follows: -- -- data IOUArray i e -- | Casts an IOUArray with one element type into one with a -- different element type. All the elements of the resulting array are -- undefined (unless you know what you're doing...). castIOUArray :: IOUArray ix a -> IO (IOUArray ix b) -- | Reads a number of Word8s from the specified Handle -- directly into an array. hGetArray :: Handle -> IOUArray Int Word8 -> Int -> IO Int -- | Writes an array of Word8 to the specified Handle. hPutArray :: Handle -> IOUArray Int Word8 -> Int -> IO () -- | Mutable boxed and unboxed arrays in the ST monad. module Data.Array.ST -- | Mutable, boxed, non-strict arrays in the ST monad. The type -- arguments are as follows: -- -- data STArray s i e :: * -> * -> * -> * -- | A safe way to create and work with a mutable array before returning an -- immutable array for later perusal. This function avoids copying the -- array before returning it - it uses unsafeFreeze internally, -- but this wrapper is a safe interface to that function. runSTArray :: Ix i => (forall s. ST s (STArray s i e)) -> Array i e -- | A mutable array with unboxed elements, that can be manipulated in the -- ST monad. The type arguments are as follows: -- -- -- -- An STUArray will generally be more efficient (in terms of both -- time and space) than the equivalent boxed version (STArray) -- with the same element type. However, STUArray is strict in its -- elements - so don't use STUArray if you require the -- non-strictness that STArray provides. data STUArray s i e -- | A safe way to create and work with an unboxed mutable array before -- returning an immutable array for later perusal. This function avoids -- copying the array before returning it - it uses unsafeFreeze -- internally, but this wrapper is a safe interface to that function. runSTUArray :: Ix i => (forall s. ST s (STUArray s i e)) -> UArray i e -- | Casts an STUArray with one element type into one with a -- different element type. All the elements of the resulting array are -- undefined (unless you know what you're doing...). castSTUArray :: STUArray s ix a -> ST s (STUArray s ix b) -- | A storable array is an IO-mutable array which stores its contents in a -- contiguous memory block living in the C heap. Elements are stored -- according to the class Storable. You can obtain the pointer to -- the array contents to manipulate elements from languages like C. -- -- It is similar to Data.Array.IO.IOUArray but slower. Its -- advantage is that it's compatible with C. module Data.Array.Storable -- | The array type data StorableArray i e -- | The pointer to the array contents is obtained by -- withStorableArray. The idea is similar to ForeignPtr -- (used internally here). The pointer should be used only during -- execution of the IO action retured by the function passed as -- argument to withStorableArray. withStorableArray :: StorableArray i e -> (Ptr e -> IO a) -> IO a -- | If you want to use it afterwards, ensure that you -- touchStorableArray after the last use of the pointer, so the -- array is not freed too early. touchStorableArray :: StorableArray i e -> IO () -- | Construct a StorableArray from an arbitrary ForeignPtr. -- It is the caller's responsibility to ensure that the ForeignPtr -- points to an area of memory sufficient for the specified bounds. unsafeForeignPtrToStorableArray :: Ix i => ForeignPtr e -> (i, i) -> IO (StorableArray i e) instance Storable e => MArray StorableArray e IO -- | Basic non-strict arrays. -- -- Note: The Data.Array.IArray module provides a more -- general interface to immutable arrays: it defines operations with the -- same names as those defined below, but with more general types, and -- also defines Array instances of the relevant classes. To use -- that more general interface, import Data.Array.IArray but not -- Data.Array. module Data.Array -- | The type of immutable non-strict (boxed) arrays with indices in -- i and elements in e. data Ix i => 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 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. array :: Ix i => (i, i) -> [(i, e)] -> Array i e -- | Construct an array from a pair of bounds and a list of values in index -- order. listArray :: Ix i => (i, i) -> [e] -> 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]
--   
-- -- 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. accumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(i, a)] -> Array i e -- | The value at the given index in an array. (!) :: Ix i => Array i e -> i -> e -- | The bounds with which an array was constructed. bounds :: Ix i => Array i e -> (i, i) -- | The list of indices of an array in ascending order. indices :: Ix i => Array i e -> [i] -- | The list of elements of an array in index order. elems :: Ix i => Array i e -> [e] -- | The list of associations of an array in index order. assocs :: Ix i => Array i e -> [(i, e)] -- | 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. (//) :: Ix i => Array i e -> [(i, e)] -> Array i e -- | 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])
--   
accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e -- | 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. ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i e -- | 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. module Data.Array.IArray -- | 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. class IArray a e bounds :: (IArray a e, Ix i) => a i e -> (i, i) -- | The type of immutable non-strict (boxed) arrays with indices in -- i and elements in e. data Ix i => Array i e :: * -> * -> * -- | 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: Data.Array.Array is a non-strict -- array type, but all of the Data.Array.Unboxed.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. array :: (IArray a e, Ix i) => (i, i) -> [(i, e)] -> a i e -- | 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. listArray :: (IArray a e, Ix i) => (i, i) -> [e] -> a i e -- | 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]
--   
accumArray :: (IArray a e, Ix i) => (e -> e' -> e) -> e -> (i, i) -> [(i, e')] -> a i e -- | Returns the element of an immutable array at the specified index. (!) :: (IArray a e, Ix i) => a i e -> i -> e -- | Returns a list of all the valid indices in an array. indices :: (IArray a e, Ix i) => a i e -> [i] -- | Returns a list of all the elements of an array, in the same order as -- their indices. elems :: (IArray a e, Ix i) => a i e -> [e] -- | Returns the contents of an array as a list of associations. assocs :: (IArray a e, Ix i) => a i e -> [(i, e)] -- | 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. (//) :: (IArray a e, Ix i) => a i e -> [(i, e)] -> a i e -- | 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])
--   
accum :: (IArray a e, Ix i) => (e -> e' -> e) -> a i e -> [(i, e')] -> a i e -- | Returns a new array derived from the original array by applying a -- function to each of the elements. amap :: (IArray a e', IArray a e, Ix i) => (e' -> e) -> a i e' -> a i e -- | Returns a new array derived from the original array by applying a -- function to each of the indices. ixmap :: (IArray a e, Ix i, Ix j) => (i, i) -> (i -> j) -> a j e -> a i e -- | Unboxed immutable arrays. module Data.Array.Unboxed -- | Arrays with unboxed elements. Instances of IArray are provided -- for UArray with certain element types (Int, -- Float, Char, etc.; see the UArray class for a -- full list). -- -- A UArray will generally be more efficient (in terms of both -- time and space) than the equivalent Data.Array.Array with the -- same element type. However, UArray is strict in its elements - -- so don't use UArray if you require the non-strictness that -- Data.Array.Array provides. -- -- Because the IArray interface provides operations overloaded -- on the type of the array, it should be possible to just change the -- array type being used by a program from say Array to -- UArray to get the benefits of unboxed arrays (don't forget to -- import Data.Array.Unboxed instead of Data.Array). data UArray i e