
I'm having difficulty compiling under 5.04 using both Arrays and UArrays: module Main where{ import Array; import Data.Array.Unboxed; array_1::UArray(Int)(Int); array_1 = (array (1,3) [(1,7),(2,8),(3,13)]); array_2::Array(Int)(Int); array_2 = (array (1,3) [(1,700),(2,800),(3,1300)]); main::IO (); main = putStrLn "hi world" } 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 Suggestions? (I would rather not have to fully qualify every occurence of array, accumArray, and ! in my program.) Ken Takusagawa

Not positive, but perhaps you could just hide things like (!), array, etc., from Unboxed since these are class methods and Unboxed is probably just reexporting what Array exports? You should also probably import Data.Array instead of just Array. -- Hal Daume III "Computer science is no more about computers | hdaume@isi.edu than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume On Wed, 24 Jul 2002, 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;
array_1::UArray(Int)(Int); array_1 = (array (1,3) [(1,7),(2,8),(3,13)]);
array_2::Array(Int)(Int); array_2 = (array (1,3) [(1,700),(2,800),(3,1300)]);
main::IO (); main = putStrLn "hi world" }
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
Suggestions? (I would rather not have to fully qualify every occurence of array, accumArray, and ! in my program.)
Ken Takusagawa
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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.
participants (3)
-
Hal Daume III
-
Ken T Takusagawa
-
Ross Paterson