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 $ dovc <- DVSM.unsafeNew (DVS.length vb)a' <- go 0 a vcreturn (a', vc)where go :: Int -> a -> DVS.MVector s c -> ST s ago i a0 vc = if i < DVS.length vbthen dolet (a1, c1) = f a0 (DVS.unsafeIndex vb i)DVSM.unsafeWrite vc i c1go (i + 1) a1 vcelse return a0{-# INLINE mapAccumL #-}The implementation should obey the following law:import qualified Data.List as Limport qualified Data.Vector.Storable as DVS(DVS.toList <$> DVS.mapAccumL f a (DVS.fromList bs)) === L.mapAccumL f a bsCheers,-John
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries