4.16. MArray

The MArray module provides a class of mutable arrays, parameterised over the array type, element type and the monad in which the array can be used:

  class (Monad m, HasBounds a) => MArray a e m where
     get     :: Ix ix => a ix e -> ix -> m e
     put     :: Ix ix => a ix e -> ix -> e -> m ()
     marray  :: Ix ix => (ix,ix) -> m (a ix e)

The get and put operations allow for reading and writing to/from the array, and marray is used for building a new array. All indices in the newly created array will contain undefined elements.

The IOArray (Section 4.14.3) and STArray (Section 4.21) types are both instances of MArray:

data STArray s ix e
instance HasBounds (STArray s)
instance MArray (STArray s) e (ST s)

data IOArray ix e
instance HasBounds IOArray
instance MArray IOArray e IO

There are also strict unboxed versions of IOArray and STArray, namely IOUArray STUArray and instances of MArray for these types with common integral element types:

data STUArray s ix e
instance HasBounds (STUArray s)
instance MArray (STArray s) Char      (ST s)
instance MArray (STArray s) Int       (ST s)
instance MArray (STArray s) Word      (ST s)
instance MArray (STArray s) Addr      (ST s)
instance MArray (STArray s) Float     (ST s)
instance MArray (STArray s) Double    (ST s)
instance MArray (STArray s) StablePtr (ST s)

data IOUArray ix e
instance HasBounds IOUArray
instance MArray IOArray Char      IO
instance MArray IOArray Int       IO
instance MArray IOArray Word      IO
instance MArray IOArray Addr      IO
instance MArray IOArray Float     IO
instance MArray IOArray Double    IO
instance MArray IOArray StablePtr IO

4.16.1. Freezing and thawing arrays

An MArray can be converted into an IArray (Section 4.12), by freezing it:

  freeze :: (Ix ix, MArray a e m, IArray b e) => a ix e -> m (b ix e)

The IArray returned is independent of the original MArray, so further modifications to the mutable version won't affect the frozen one. The usual implementation of freeze is to make a copy of the array.

In many cases, the additional copy is unnecessary, for example when freezing is the last operation on the mutable version of the array. For these cases, an unsafe version of freeze is provided which may not copy[1] the array:

  unsafeFreeze :: (Ix ix, MArray a e m, IArray b e) => a ix e -> m (b ix e)

The dual to freeze is thaw, which converts an IArray into an MArray:

  thaw :: (Ix ix, IArray a e, MArray b e m) => a ix e -> m (b ix e)

As with freeze, thaw needs to make a copy of the array. For the cases when you know the copy is unnecessary, we also provide unsafeThaw:

  unsafeThaw :: (Ix ix, IArray a e, MArray b e m) => a ix e -> m (b ix e)

4.16.2. Useful combinators

MArray also provides versions of the following standard array combinators. Note that they have slightly different types from the versions in Array and IArray, mostly to accomodate the requirement that an MArray must be used within a monad:

assocs    :: (Ix ix, MArray a e m) => a ix e -> m [(ix,e)]

indices   :: (Ix ix, IArray a e) => a ix e -> [ix]

(//)      :: (Ix ix, MArray a e m) => a ix e -> [(ix,e)] -> m ()

amap      :: (Ix ix, MArray a x m, MArray a y m) => 
                (x->y) -> a ix x -> m (a ix y)

listArray :: (Ix ix, MArray a e m) => (ix,ix) -> [e] -> m (a ix e)
	  
elems     :: (Ix ix, MArray a e m) => a ix e -> m [e]
	  
ixmap     :: (Ix ix, Ix iy, MArray a e m) => 
	  	   (ix,ix) -> (ix->iy) -> a iy e -> m (a ix e)

Notes

[1]

The default implementation of unsafeFreeze is freeze, but it is expected that specialised versions which omit the copy are provided for the common array types.