[Haskell-cafe] Data.Foldable UArray

Marcus D. Gabriel marcus at gabriel.name
Sun Feb 23 22:17:49 UTC 2014


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 <marcus at gabriel.name <mailto:marcus at 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/d81bf2fe5ef4ee5957f3a5c54af07a00637c932f/src/Data/MonoTraversable.hs#L502 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140223/11a1d82c/attachment.html>


More information about the Haskell-Cafe mailing list