Using UArray and Array

Ross Paterson ross@soi.city.ac.uk
Wed, 24 Jul 2002 22:02:16 +0100


On Wed, Jul 24, 2002 at 02:35:37PM -0400, Ken T Takusagawa wrote:
> I'm having difficulty compiling under 5.04 using both Arrays
> and UArrays:
> 
> module Main  where{
> import Array;
> import Data.Array.Unboxed;
> 
> [...]
> 
> This gets me the errors
>     Ambiguous occurrence `array'
>     It could refer to either `Data.Array.Base.array',
> imported from Data.Array.Unboxed at arrayfailx.hs:6
> 		          or `GHC.Arr.array', imported from
> Array at arrayfailx.hs:5

Short answer: just say

	import Array(Array)
	import Data.Array.Unboxed

Long answer:
It is a bit subtle, and maybe the docs could explain it more.
In Data.Array (which Array imports and re-exports), there is

	array :: (Ix a) => (a,a) -> [(a,b)] -> Array a b

as required by Haskell 98.  (Actually it's imported from GHC.Arr.)
In Data.Array.IArray (imported and re-exported by Data.Array.UArray)
there is a function of the same name with the type

	array :: (IArray a e, Ix i) => (i,i) -> [(i, e)] -> a i e

(actually imported from Data.Array.Base.)  This is a generalization of
the previous function, because there is an instance

	instance IArray Array e

and similarly for (!), accum and the rest.

Data.Array.Unboxed then brings in Unboxed, with instances

	instance IArray UArray Bool
	IArray UArray Char
	IArray UArray Int
	etc.

The result of all this is that you need only Array from Data.Array,
and you can use the more general functions on both Array and UArray.
In the case of Array they are identical to the Data.Array ones.