Proposal to add mapAccumL function to vector package

John Ky newhoggy at gmail.com
Thu Nov 8 11:30:30 UTC 2018


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20181108/17f2fdb8/attachment.html>


More information about the Libraries mailing list