Data.Foldable UArray

Hello, I wanted to make a simple Data.Foldable UArray, and I naively modelled it on
instance Ix i => Foldable (Array i) where foldr f z = Prelude.foldr f z . elems
with, of course,
instance Ix i => Foldable (UArray i) where foldr f z = Prelude.foldr f z . elems
which did not work yielding the following type message Could not deduce (IArray UArray a) arising from a use of `elems' from the context (Ix i) bound by the instance declaration at ... Possible fix: add an instance declaration for (IArray UArray a) In the second argument of `(.)', namely `elems' In the expression: Data.List.foldr f z . elems In an equation for `foldr': foldr f z = Data.List.foldr f z . elems I clearly do not understand something because I cannot make this work, and I am not sure why. With the Haskell type system or even with ghc extensions, can one even make a Data.Foldable UArray? If so, how? Thanks in advance, - Marcus

not every value can be unboxed. A good example for understanding this would
be looking at the Unboxed Modules in the Vector package
On Thu, Feb 20, 2014 at 4:12 PM, Marcus D. Gabriel
Hello,
I wanted to make a simple Data.Foldable UArray, and I naively modelled it on
instance Ix i => Foldable (Array i) where foldr f z = Prelude.foldr f z . elems
with, of course,
instance Ix i => Foldable (UArray i) where foldr f z = Prelude.foldr f z . elems
which did not work yielding the following type message
Could not deduce (IArray UArray a) arising from a use of `elems' from the context (Ix i) bound by the instance declaration at ... Possible fix: add an instance declaration for (IArray UArray a) In the second argument of `(.)', namely `elems' In the expression: Data.List.foldr f z . elems In an equation for `foldr': foldr f z = Data.List.foldr f z . elems
I clearly do not understand something because I cannot make this work, and I am not sure why.
With the Haskell type system or even with ghc extensions, can one even make a Data.Foldable UArray? If so, how?
Thanks in advance, - Marcus _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 20, 2014 at 11:12 PM, Marcus D. Gabriel
Hello,
I wanted to make a simple Data.Foldable UArray, and I naively modelled it on
instance Ix i => Foldable (Array i) where foldr f z = Prelude.foldr f z . elems
with, of course,
instance Ix i => Foldable (UArray i) where foldr f z = Prelude.foldr f z . elems
which did not work yielding the following type message
Could not deduce (IArray UArray a) arising from a use of `elems' from the context (Ix i) bound by the instance declaration at ... Possible fix: add an instance declaration for (IArray UArray a) In the second argument of `(.)', namely `elems' In the expression: Data.List.foldr f z . elems In an equation for `foldr': foldr f z = Data.List.foldr f z . elems
I clearly do not understand something because I cannot make this work, and I am not sure why.
With the Haskell type system or even with ghc extensions, can one even make a Data.Foldable UArray? If so, how?
Thanks in advance, - Marcus
You could create an instance of MonoFoldable for UArray, similar to how the instance for unboxed vectors works[1]. There's no inherent reason why the Array instances don't exist there yet, I simply didn't get around to adding them yet. [1] https://github.com/snoyberg/mono-traversable/blob/d81bf2fe5ef4ee5957f3a5c54a...

For the record, Michael's suggestion worked for me, and it was quite space and time efficient. Here is a code fragment in case someone like me is looking for this:
{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
import Data.Array.IArray (IArray) import Data.Array.Unboxed (UArray, (!), array, elems, bounds) import Data.Ix (Ix) import qualified Data.List as L import qualified Data.Foldable.Mono as F
instance (Ix i, IArray UArray e) => F.MFoldable (UArray i e) where type Elem (UArray i e) = e foldl f z = L.foldl f z . elems foldl' f z = L.foldl' f z . elems foldl1 f = L.foldl1 f . elems foldr f z = L.foldr f z . elems foldr1 f = L.foldr1 f . elems
To be honest, I was aware of TypeFamilies, but they are new to me so I need a little study. Cheers, - Marcus On 21/02/2014 07:06, Michael Snoyman wrote:
On Thu, Feb 20, 2014 at 11:12 PM, Marcus D. Gabriel
mailto:marcus@gabriel.name> wrote: Hello,
I wanted to make a simple Data.Foldable UArray, and I naively modelled it on
> instance Ix i => Foldable (Array i) where > foldr f z = Prelude.foldr f z . elems
with, of course,
> instance Ix i => Foldable (UArray i) where > foldr f z = Prelude.foldr f z . elems
which did not work yielding the following type message
Could not deduce (IArray UArray a) arising from a use of `elems' from the context (Ix i) bound by the instance declaration at ... Possible fix: add an instance declaration for (IArray UArray a) In the second argument of `(.)', namely `elems' In the expression: Data.List.foldr f z . elems In an equation for `foldr': foldr f z = Data.List.foldr f z . elems
I clearly do not understand something because I cannot make this work, and I am not sure why.
With the Haskell type system or even with ghc extensions, can one even make a Data.Foldable UArray? If so, how?
Thanks in advance, - Marcus
You could create an instance of MonoFoldable for UArray, similar to how the instance for unboxed vectors works[1]. There's no inherent reason why the Array instances don't exist there yet, I simply didn't get around to adding them yet.
[1] https://github.com/snoyberg/mono-traversable/blob/d81bf2fe5ef4ee5957f3a5c54a...

On Thu, Feb 20, 2014 at 10:12:54PM +0100, Marcus D. Gabriel wrote:
Hello,
I wanted to make a simple Data.Foldable UArray, and I naively modelled it on
instance Ix i => Foldable (Array i) where foldr f z = Prelude.foldr f z . elems
with, of course,
instance Ix i => Foldable (UArray i) where foldr f z = Prelude.foldr f z . elems
which did not work yielding the following type message
Could not deduce (IArray UArray a) arising from a use of `elems' [...]
The problem is that the argument 'e' in 'UArray i e' is a phantom type argument used only for looking up the relevant instance of 'IArray'. It doesn't actually have anything to do with the underlying contents of the array, which is basically just a 'ByteString'. Since all 'Foldable' functions factor through 'toList', you can't go too wrong by using '(foldableFunction . toList) myArray' wherever you would have wanted to use 'foldableFunction myArray'. Tom

Hello Tom, Basically, I follow what you have written but ... We have
Prelude> :k Data.Array.Unboxed.UArray Data.Array.Unboxed.UArray :: * -> * -> *
which is why I tried my first naive solution. I note that we have also
Prelude> :k Data.Array.IArray.IArray Data.Array.IArray.IArray :: (* -> * -> *) -> * -> Constraint
This last one I do not follow. A short explanation and/or a pointer to some documentation would help. Thanks, - Marcus On 21/02/2014 09:47, Tom Ellis wrote:
On Thu, Feb 20, 2014 at 10:12:54PM +0100, Marcus D. Gabriel wrote:
Hello,
I wanted to make a simple Data.Foldable UArray, and I naively modelled it on
instance Ix i => Foldable (Array i) where foldr f z = Prelude.foldr f z . elems with, of course,
instance Ix i => Foldable (UArray i) where foldr f z = Prelude.foldr f z . elems which did not work yielding the following type message
Could not deduce (IArray UArray a) arising from a use of `elems' [...]
The problem is that the argument 'e' in 'UArray i e' is a phantom type argument used only for looking up the relevant instance of 'IArray'. It doesn't actually have anything to do with the underlying contents of the array, which is basically just a 'ByteString'.
Since all 'Foldable' functions factor through 'toList', you can't go too wrong by using '(foldableFunction . toList) myArray' wherever you would have wanted to use 'foldableFunction myArray'.
Tom

On Fri, Feb 21, 2014 at 09:30:12PM +0100, Marcus D. Gabriel wrote:
Prelude> :k Data.Array.Unboxed.UArray Data.Array.Unboxed.UArray :: * -> * -> *
which is why I tried my first naive solution.
Hi Marcus, This means that 'UArray' is a type constructor of two arguments, i.e. for types 'i' and 'e' UArray i e is a type. It is an array that is indexed by elements of type 'i' (which would typically be something like 'Int' in practice). It is also declaring that ostensibly it contains unboxed values of type 'e' (which in practice could be 'Bool', 'Char', 'Int', 'Double' and many other things besides). For example, a type of an unboxed array you might use could be UArray Int Double an array of doubles indexed by ints. However if you look at the definition of 'UArray' http://hackage.haskell.org/package/array-0.5.0.0/docs/src/Data-Array-Base.ht... you will see that the 'e' type parameter is not actually used in the definition of the datatype! It is a so-called "phantom type". The datatype doesn't "actually" contain any 'e's. Instead it contains a ByteString into which certain 'e's can be written in a way which is in a sense "unsafe" but only a "safe" interface is provided. (See below).
I note that we have also
Prelude> :k Data.Array.IArray.IArray Data.Array.IArray.IArray :: (* -> * -> *) -> * -> Constraint
This last one I do not follow. A short explanation and/or a pointer to some documentation would help.
'IArray' is a typeclass, in this case essentially used as means of providing a standard interface to arrays. The kind signature above means that the interface is parametrised by the array constructor (of kind * -> * -> *, like UArray, see above) and the type of the index. If you give 'IArray' an array constructor and an index type you get a 'Constraint', in this case a typeclass context which essentially provides you with an interface to access your 'UArray' with. However, these constructions are not suitible for making an instance of Foldable, because Foldable would require implementing functions that are uniform in the way they treat the type argument 'e', and as we've seen, the usage of 'e' in the datatype and interface is far from uniform. Hope that helps, Tom

Yes, Tom it does help. I will not cogitate on this in the morning. - Marcus On 21/02/2014 22:14, Tom Ellis wrote:
On Fri, Feb 21, 2014 at 09:30:12PM +0100, Marcus D. Gabriel wrote:
Prelude> :k Data.Array.Unboxed.UArrays Data.Array.Unboxed.UArray :: * -> * -> * which is why I tried my first naive solution. Hi Marcus,
This means that 'UArray' is a type constructor of two arguments, i.e. for types 'i' and 'e'
UArray i e
is a type. It is an array that is indexed by elements of type 'i' (which would typically be something like 'Int' in practice). It is also declaring that ostensibly it contains unboxed values of type 'e' (which in practice could be 'Bool', 'Char', 'Int', 'Double' and many other things besides). For example, a type of an unboxed array you might use could be
UArray Int Double
an array of doubles indexed by ints. However if you look at the definition of 'UArray'
http://hackage.haskell.org/package/array-0.5.0.0/docs/src/Data-Array-Base.ht...
you will see that the 'e' type parameter is not actually used in the definition of the datatype! It is a so-called "phantom type". The datatype doesn't "actually" contain any 'e's. Instead it contains a ByteString into which certain 'e's can be written in a way which is in a sense "unsafe" but only a "safe" interface is provided. (See below).
I note that we have also
Prelude> :k Data.Array.IArray.IArray Data.Array.IArray.IArray :: (* -> * -> *) -> * -> Constraint This last one I do not follow. A short explanation and/or a pointer to some documentation would help. 'IArray' is a typeclass, in this case essentially used as means of providing a standard interface to arrays. The kind signature above means that the interface is parametrised by the array constructor (of kind * -> * -> *, like UArray, see above) and the type of the index. If you give 'IArray' an array constructor and an index type you get a 'Constraint', in this case a typeclass context which essentially provides you with an interface to access your 'UArray' with.
However, these constructions are not suitible for making an instance of Foldable, because Foldable would require implementing functions that are uniform in the way they treat the type argument 'e', and as we've seen, the usage of 'e' in the datatype and interface is far from uniform.
Hope that helps,
Tom

Since all 'Foldable' functions factor through 'toList', you can't go too wrong by using '(foldableFunction . toList) myArray' wherever you would have wanted to use 'foldableFunction myArray'.
Isn't this going to be rather inefficient? Presumably the point of using an array is to avoid using lists for an application where they are not appropriate?

On Sat, Feb 22, 2014 at 07:15:22PM +0000, Dominic Steinitz wrote:
Since all 'Foldable' functions factor through 'toList', you can't go too wrong by using '(foldableFunction . toList) myArray' wherever you would have wanted to use 'foldableFunction myArray'.
Isn't this going to be rather inefficient? Presumably the point of using an array is to avoid using lists for an application where they are not appropriate?
(I'll take this opportunity to correct myself: I meant 'foldableFunction . elems', not 'foldableFunction . toList') Marcus's proposed Foldable instance used 'elems' anyway, and furthermore the public API to UArray (which is just IArray) provides no other suitable means of folding the elements, so there's hardly something "more efficient" to compare to. It would be interesting to see if a more efficient implementation of 'foldr' and friends could be written using the internal interface, but I wouldn't be terribly surprised if it were no better that the naive approach plus list fusion. (I'm far from expert though). Tom

On Sat, Feb 22, 2014 at 10:17 PM, Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Sat, Feb 22, 2014 at 07:15:22PM +0000, Dominic Steinitz wrote:
Since all 'Foldable' functions factor through 'toList', you can't go too wrong by using '(foldableFunction . toList) myArray' wherever you would have wanted to use 'foldableFunction myArray'.
Isn't this going to be rather inefficient? Presumably the point of using an array is to avoid using lists for an application where they are not appropriate?
(I'll take this opportunity to correct myself: I meant 'foldableFunction . elems', not 'foldableFunction . toList')
Marcus's proposed Foldable instance used 'elems' anyway, and furthermore the public API to UArray (which is just IArray) provides no other suitable means of folding the elements, so there's hardly something "more efficient" to compare to.
It would be interesting to see if a more efficient implementation of 'foldr' and friends could be written using the internal interface, but I wouldn't be terribly surprised if it were no better that the naive approach plus list fusion. (I'm far from expert though).
It's not exactly the same thing, but I recently sent a pull request for a more efficient version of mapM_ in bytestring[1] which avoids an intermediate list representation. This implementation is already used in both mono-traversable's omapM_ and Data.Conduit.Binary.mapM_, and I've seen significant performance gain by using it. I'd imagine the same would be true for UArray. At the very least, I'd try using explicit array indexing instead of converting to a list and see how that affects performance. [1] https://github.com/haskell/bytestring/pull/9

My intuition is that Tom is correct in his supposition.
-- Performance comparaisons arrayFoldl' :: (Ix i, IArray a e) => (t -> e -> t) -> t -> a i e -> t arrayFoldl' f z = L.foldl' f z . elems
arrayFold :: (Enum i, Ix i, IArray a e) => (t -> e -> t) -> t -> a i e -> t arrayFold f z a = let (lo, hi) = bounds a arrayFold_ i z' = if i <= hi then arrayFold_ (succ i) (f z' (a!i) ) else z' in arrayFold_ lo z
If you are willing to accept the (Enum i), then I did not observe any differences in space and time performance between the two functions above with the '-O2' option and using UArray. Note I used the word experience, not test. - Marcus On 23/02/2014 05:56, Michael Snoyman wrote:
On Sat, Feb 22, 2014 at 10:17 PM, Tom Ellis
mailto:tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote: On Sat, Feb 22, 2014 at 07:15:22PM +0000, Dominic Steinitz wrote: > > Since all 'Foldable' functions factor through 'toList', you can't go too > > wrong by using '(foldableFunction . toList) myArray' wherever you would have > > wanted to use 'foldableFunction myArray'. > > Isn't this going to be rather inefficient? Presumably the point of > using an array is to avoid using lists for an application where they > are not appropriate?
(I'll take this opportunity to correct myself: I meant 'foldableFunction . elems', not 'foldableFunction . toList')
Marcus's proposed Foldable instance used 'elems' anyway, and furthermore the public API to UArray (which is just IArray) provides no other suitable means of folding the elements, so there's hardly something "more efficient" to compare to.
It would be interesting to see if a more efficient implementation of 'foldr' and friends could be written using the internal interface, but I wouldn't be terribly surprised if it were no better that the naive approach plus list fusion. (I'm far from expert though).
It's not exactly the same thing, but I recently sent a pull request for a more efficient version of mapM_ in bytestring[1] which avoids an intermediate list representation. This implementation is already used in both mono-traversable's omapM_ and Data.Conduit.Binary.mapM_, and I've seen significant performance gain by using it. I'd imagine the same would be true for UArray. At the very least, I'd try using explicit array indexing instead of converting to a list and see how that affects performance.
participants (5)
-
Carter Schonwald
-
Dominic Steinitz
-
Marcus D. Gabriel
-
Michael Snoyman
-
Tom Ellis