4.17. IArray

This module provides a family of immutable array data types, and is intended to be a replacement for Haskell's standard Array module. In addition, a family of mutable array types is provided by the MArray module (see Section 4.21).

4.17.1. IArray and HasBounds type classes

Two new type classes are provided, HasBounds and IArray:

  class HasBounds a where
     bounds :: Ix ix => a ix e -> (ix,ix)

  class HasBounds a => IArray a e where
     array :: Ix ix => (ix,ix) -> [(ix,e)] -> a ix e	
     (!)   :: Ix ix => a ix e -> ix -> e
     (//)  :: Ix ix => a ix e -> [(ix,e)] -> a ix e

  instance HasBounds (Array.Array)
  instance IArray Array.Array e

where the type variable a denotes the array type constructor, ix denotes the index type, and e is the element type.

The Array, (!), (//) and bounds methods provided are exactly analoguous to those provided by the Haskell 98 Array module, and indeed instances of HasBounds and IArray are provided for the standard Array type.

4.17.2. UArray: immutable unboxed arrays

The UArray type is a flat, strict, unboxed array type, which has instances of IArray for common integral element types:

  data UArray ix e
  instance HasBounds UArray
  instance IArray UArray Bool
  instance IArray UArray Char
  instance IArray UArray Int
  instance IArray UArray Word
  instance IArray UArray Addr
  instance IArray UArray (Ptr a)
  instance IArray UArray Float
  instance IArray UArray Double
  instance IArray UArray (StablePtr a)
  instance IArray UArray Int8
  instance IArray UArray Int16
  instance IArray UArray Int32
  instance IArray UArray Int64
  instance IArray UArray Word8
  instance IArray UArray Word16
  instance IArray UArray Word32
  instance IArray UArray Word64

The idea here is that any code which currently uses a standard non-strict polymorphic Array with one of these element types can be easily converted to use UArray by simply importing IArray and changing the type of the array from Array to UArray. The application will then get the performance benefit of strict unboxed arrays, whithout making significant changes to the existing code.

4.17.3. Useful combinators

The IArray module also provides versions of the standard array combinators from Haskell 98's Array module:

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

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

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

  elems      :: (Ix ix, IArray a e) => a ix e -> [e]
  
  amap       :: (Ix ix, IArray a x, IArray a y) => 
  		   (x -> y) -> a ix x -> a ix y

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

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

  ixmap      :: (Ix ix, Ix iy) => 
  		  (ix,ix) -> (ix->iy) -> a iy e -> a ix e