UArray
Frederik Eaton
frederik at ofb.net
Sun Mar 12 13:39:13 EST 2006
I was trying to track down the problem with this piece of code:
instance (Elt k, IxB a, Eq a, Eq k) => Num (Vector k a) where
(+) = vmap2 (+)
(-) = vmap2 (-)
(*) = vmap2 (*)
negate = vmap negate
signum = vmap signum
abs = vmap abs
fromInteger n = vconst $ fromInteger n
Vector2.hs:246:0:
Could not deduce (Eq (UArray a k)) from the context (Elt k, IxB a, Eq a, Eq k)
arising from the superclasses of an instance declaration at Vector2.hs:246:0
Probable fix:
add (Eq (UArray a k)) to the instance declaration superclass context
or add an instance declaration for (Eq (UArray a k))
In the instance declaration for `Num (Vector k a)'
So it appears that here is another barrier to using UArray
polymorphically. Am I the first user of this interface?
In Data/Array/Base.hs it says:
eqUArray :: (IArray UArray e, Ix i, Eq e) => UArray i e -> UArray i e -> Bool
eqUArray arr1@(UArray l1 u1 _) arr2@(UArray l2 u2 _) =
if rangeSize (l1,u1) == 0 then rangeSize (l2,u2) == 0 else
l1 == l2 && u1 == u2 &&
and [unsafeAt arr1 i == unsafeAt arr2 i | i <- [0 .. rangeSize (l1,u1) - 1]]
...
instance Ix ix => Eq (UArray ix Bool) where
(==) = eqUArray
instance Ix ix => Eq (UArray ix Bool) where
(==) = eqUArray
instance Ix ix => Eq (UArray ix Char) where
(==) = eqUArray
instance Ix ix => Eq (UArray ix Int) where
(==) = eqUArray
instance Ix ix => Eq (UArray ix Word) where
(==) = eqUArray
...
etc.
Why define separate instances when one could just define one
equivalent one:
instance (Ix ix, Eq e, IArray UArray e) => Eq (UArray ix e)
(==) = eqUArray
???
The same question applies to the Ord instances in that file.
I can give an answer *why not* do this: it makes UArray even more
unusable. UArrays which are polymorphic in their element types cannot
be compared. Here is another patch, please apply:
--- /home/frederik/ghc-6.4/libraries/base/Data/Array/Unboxed.hs.old 2006-03-12 18:34:14.000000000 +0000
+++ /home/frederik/ghc-6.4/libraries/base/Data/Array/Unboxed.hs 2006-03-12 18:35:32.000000000 +0000
@@ -10,6 +10,9 @@
--
-- Unboxed immutable arrays.
--
+-- Beware that these arrays are generally not usable polymorphically
+-- because of problems with Eq and Ord instances.
+--
-----------------------------------------------------------------------------
module Data.Array.Unboxed (
Confused,
Frederik
On Sun, Mar 12, 2006 at 02:58:42AM +0000, Frederik Eaton wrote:
> I see. The solutions on that thread, i.e.:
>
> http://www.mail-archive.com/haskell%40haskell.org/msg17085.html
>
> would seem to require me to at least declare an instance of some
> class, for every type that I want to support. So the short answer to
> "I'm trying to figure out how to use STUArray. Is it possible to let
> it be polymorphic?" appears to be "No".
>
> Perhaps some sort of warning in the documentation for STUArray is in
> order, until Bulat's code can be incorporated?
>
> By the way, why make the distinction between unboxable types and
> "other" types in the first place? E.g., just because I want something
> to work quickly on "Int", doesn't mean that I don't want it to work at
> all on "String". It seems that there could be a default "IArray UArray
> e" instance which just implements a regular Array behind the scenes.
>
> Frederik
>
> On Fri, Mar 10, 2006 at 11:49:10PM +0100, Benjamin Franksen wrote:
> > On Friday 10 March 2006 23:01, Frederik Eaton wrote:
> > > I'm trying to figure out how to use STUArray. Is it possible to let
> > > it be polymorphic?
> >
> > Hi Frederik
> >
> > I think this thread (and the one it referres to) provide a solution:
> >
> > http://www.mail-archive.com/haskell%40haskell.org/msg17081.html
> >
> > Ben
> > --
> > There are three kinds of programmers: those who make off by one errors,
> > and those who don't.
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
> --
> http://ofb.net/~frederik/
>
--
http://ofb.net/~frederik/
More information about the Libraries
mailing list