Proposal to add mapAccumL function to vector package

Carter Schonwald carter.schonwald at gmail.com
Thu Nov 8 14:17:58 UTC 2018


I thought about it a teeny bit more

This should be trivially definable using mapM or equivalent using state t

Have you tried doing that simple high level definition?  I think that works
with vector fusion quite nicely.

... ohhh. I see.  There’s two vectors of inputs.  I’ll have to think about
this more.

On Thu, Nov 8, 2018 at 8:14 AM Carter Schonwald <carter.schonwald at gmail.com>
wrote:

> Hey John
> :
> I’m happy to help you contribute to to vector.
>
> 1). This might not actually be needed with stream fusion on  ... though
> perhaps this sort of shared computation needs to be its own combinators
> because of the sharing meaning that the stream fusion on map and foldl
> might not work. (Have you tried doing let x = map ... in let y = foldl ...
> in something with x and y? Even eg just writing map accum l in terms of
> just that? It could very well fuse ... though I don’t think it can with the
> current vector fusion framework. Though I think one of the more exotic
> fusion frameworks Amos Robinson did a few years ago could handle that
> fusion.   Sadly that one requires an ILP solver at compile time.  But
> there’s some tricks I think we could do )
>
> 2) writing it in stream fusion form / as map accum l for streams will
> actually be simpler I think
>
> 3) put a ticket on our GitHub. I’ve a huge backlog (life and stuff got me
> a bit slow), but this sounds like a super reasonable feature request
>
>
>
> On Thu, Nov 8, 2018 at 6:31 AM John Ky <newhoggy at gmail.com> wrote:
>
>> Hello,
>>
>> I'd like to add the mapAccumL function to the vector package.
>>
>> Specifically the Data.Vector.Storable module, but it would also be
>> useful other vector modules.
>>
>> This is my attempt at an implementation:
>>
>> {-# LANGUAGE ScopedTypeVariables #-}
>>
>> mapAccumL :: forall a b c. (Storable b, Storable c)
>> => (a -> b -> (a, c))
>> -> a
>> -> DVS.Vector b
>> -> (a, DVS.Vector c)
>> mapAccumL f a vb = DVS.createT $ do
>> vc <- DVSM.unsafeNew (DVS.length vb)
>> a' <- go 0 a vc
>> return (a', vc)
>> where go :: Int -> a -> DVS.MVector s c -> ST s a
>> go i a0 vc = if i < DVS.length vb
>> then do
>> let (a1, c1) = f a0 (DVS.unsafeIndex vb i)
>> DVSM.unsafeWrite vc i c1
>> go (i + 1) a1 vc
>> else return a0
>> {-# INLINE mapAccumL #-}
>>
>> The implementation should obey the following law:
>>
>> import qualified Data.List as L
>> import qualified Data.Vector.Storable as DVS
>>
>> (DVS.toList <$> DVS.mapAccumL f a (DVS.fromList bs)) === L.mapAccumL f a
>> bs
>>
>> Cheers,
>>
>> -John
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20181108/d5aec8fb/attachment.html>


More information about the Libraries mailing list