Using UArray and Array

Hal Daume III hdaume@ISI.EDU
Wed, 24 Jul 2002 11:44:45 -0700 (PDT)


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
>