Proposal: bring BBP to Arrays

It looks like Array and IArray have missed some important BBP bits. In particular, we have great ways to build arrays out of lists, but not out of other Foldables. I think we can fix IArray by adding new methods. I think we can fix up Array by adding some functions to Data.Array or by sticking Data.Foldable underneath GHC.Arr and sticking them in there (the low-level fiddling involved would be a better match for GHC.Arr).

On Thu, Nov 13, 2014 at 1:17 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 12 Nov 2014, David Feuer wrote:
It looks like Array and IArray have missed some important BBP bits.
What is BBP?
BBP: Foldable/Traversable. As part of the so-called "Burning-Bridges Proposal", the monomorphic definitions in Prelude/Data.List/Control.Monad that conflict with those from Data.Foldable and Data.Traversable have been replaced by their respective ones from Data.Foldable/Data.Traversable. This will be in 7.10

GHC.Arr defines
{-# INLINE unsafeArray' #-}
unsafeArray' :: Ix i => (i,i) -> Int -> [(Int, e)] -> Array i e
unsafeArray' (l,u) n@(I# n#) ies = runST (ST $ \s1# ->
case newArray# n# arrEleBottom s1# of
(# s2#, marr# #) ->
foldr (fill marr#) (done l u n marr#) ies s2#)
This is a critical array-building function, but it only works for lists.
I'd like to change that. The two things that would have to change would be
the type signature, which would become
unsafeArray' :: (Foldable f, Ix i) => (i,i) -> Int -> f (Int, e) -> Array i
e
and its choice of foldr, from GHC.List.foldr to Data.Foldable.foldr.
On Thu, Nov 13, 2014 at 4:22 AM, Bob Ippolito
On Thu, Nov 13, 2014 at 1:17 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 12 Nov 2014, David Feuer wrote:
It looks like Array and IArray have missed some important BBP bits.
What is BBP?
From https://ghc.haskell.org/trac/ghc/wiki/Status/Oct14 -
BBP: Foldable/Traversable. As part of the so-called "Burning-Bridges Proposal", the monomorphic definitions in Prelude/Data.List/Control.Monad that conflict with those from Data.Foldable and Data.Traversable have been replaced by their respective ones from Data.Foldable/Data.Traversable. This will be in 7.10
participants (3)
-
Bob Ippolito
-
David Feuer
-
Henning Thielemann