I have wanted this for a while, and would prefer imap/itraverse as names. Iirc this is how the similar functions in vector are named

On Sat, Aug 17, 2019, 10:47 AM Dmitriy Kovanikov <kovanikov@gmail.com> wrote:
I want to point out that there already exist Haskell package `ilist` that provides indexed versions of each function for the list from `base`:

http://hackage.haskell.org/package/ilist

This package comes with optimized implementations and custom fusion rules. For example `mapWithIndex` is called `imap` and is implemented like this:

{- |
/Subject to fusion./
-}
imap :: (Int -> a -> b) -> [a] -> [b]
imap f ls = go 0# ls
  where
    go i (x:xs) = f (I# i) x : go (i +# 1#) xs
    go _ _ = []
{-# NOINLINE [1] imap #-}
imapFB
  :: (b -> t -> t) -> (Int -> a -> b) -> a -> (Int# -> t) -> Int# -> t
imapFB c f = \x r k -> f (I# k) x `c` r (k +# 1#)
{-# INLINE [0] imapFB #-}

{-# RULES
"imap"       [~1] forall f xs.    imap f xs = build (\c n -> foldr (imapFB c f) (\_ -> n) xs 0#)
"imapList"   [1]  forall f xs.    foldr (imapFB (:) f) (\_ -> []) xs 0# = imap f xs
  #-}

I'm not trying to say that we shouldn't have `mapWithIndex` in `base`. But the implementation for lists already exists and the inspiration about the implementation can be taken from it.


On Sat, Aug 17, 2019 at 9:17 AM David Feuer <david.feuer@gmail.com> wrote:
mapWithIndex :: (Int -> a -> b) -> [a] -> [b]
mapWithIndex f = zipWith f [0..]

traverseWithIndex :: Applicative f => (Int -> a -> f b) -> [a] -> f [b]
traverseWithIndex f = sequenceA . mapWithIndex

The real implementation of mapWithIndex (and therefore of traverseWithIndex) can be a "good consumer" for list fusion. mapWithIndex can be a "good producer" as well (which the naive implementation already accomplishes).

Similar functions (with these or similar names) are already common in packages like vector, containers, unordered-containers, and primitive.

A more general function would merge zipping with unfolding:

zipWithUnfoldr :: (a -> b -> c) -> (s -> Maybe (b, s)) -> [a] -> s -> [c]
zipWithUnfoldr f g as s = zipWith f as (unfoldr g s)

But this doesn't seem like the friendliest or most obvious user interface, so I am not proposing to add it to base.
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries