{-# LANGUAGE CPP         #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe        #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
-- | Indexed Traversables
module Data.Traversable.WithIndex (
    -- * Indexed Traversables
    TraversableWithIndex(..),
    -- * Indexed Traversable Combinators
    ifor,
    imapM,
    iforM,
    imapAccumR,
    imapAccumL,
    -- * Default implementations
    imapDefault,
    ifoldMapDefault,
) where

import Prelude (Monad (..), flip)

import Control.Applicative           (Applicative (..), WrappedMonad (..))
import Control.Applicative.Backwards (Backwards (..))
import Data.Tuple                    (swap)

import qualified Control.Monad.Trans.State.Lazy as Lazy

import WithIndex

-- | Traverse with an index (and the arguments flipped).
--
-- @
-- 'for' a ≡ 'ifor' a '.' 'const'
-- 'ifor' ≡ 'flip' 'itraverse'
-- @
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
ifor :: t a -> (i -> a -> f b) -> f (t b)
ifor = ((i -> a -> f b) -> t a -> f (t b))
-> t a -> (i -> a -> f b) -> f (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (i -> a -> f b) -> t a -> f (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse
{-# INLINE ifor #-}

-- | Map each element of a structure to a monadic action,
-- evaluate these actions from left to right, and collect the results, with access
-- the index.
--
-- When you don't need access to the index 'mapM' is more liberal in what it can accept.
--
-- @
-- 'mapM' ≡ 'imapM' '.' 'const'
-- @
imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
imapM :: (i -> a -> m b) -> t a -> m (t b)
imapM i -> a -> m b
f = WrappedMonad m (t b) -> m (t b)
forall (m :: * -> *) a. WrappedMonad m a -> m a
unwrapMonad (WrappedMonad m (t b) -> m (t b))
-> (t a -> WrappedMonad m (t b)) -> t a -> m (t b)
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. (i -> a -> WrappedMonad m b) -> t a -> WrappedMonad m (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse (\i
i -> m b -> WrappedMonad m b
forall (m :: * -> *) a. m a -> WrappedMonad m a
WrapMonad (m b -> WrappedMonad m b) -> (a -> m b) -> a -> WrappedMonad m b
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. i -> a -> m b
f i
i)
{-# INLINE imapM #-}

-- | Map each element of a structure to a monadic action,
-- evaluate these actions from left to right, and collect the results, with access
-- its position (and the arguments flipped).
--
-- @
-- 'forM' a ≡ 'iforM' a '.' 'const'
-- 'iforM' ≡ 'flip' 'imapM'
-- @
iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)
iforM :: t a -> (i -> a -> m b) -> m (t b)
iforM = ((i -> a -> m b) -> t a -> m (t b))
-> t a -> (i -> a -> m b) -> m (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (i -> a -> m b) -> t a -> m (t b)
forall i (t :: * -> *) (m :: * -> *) a b.
(TraversableWithIndex i t, Monad m) =>
(i -> a -> m b) -> t a -> m (t b)
imapM
{-# INLINE iforM #-}

-- | Generalizes 'Data.Traversable.mapAccumR' to add access to the index.
--
-- 'imapAccumROf' accumulates state from right to left.
--
-- @
-- 'Control.Lens.Traversal.mapAccumR' ≡ 'imapAccumR' '.' 'const'
-- @
imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumR :: (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumR i -> s -> a -> (s, b)
f s
s0 t a
a = (t b, s) -> (s, t b)
forall a b. (a, b) -> (b, a)
swap (State s (t b) -> s -> (t b, s)
forall s a. State s a -> s -> (a, s)
Lazy.runState (Backwards (StateT s Identity) (t b) -> State s (t b)
forall k (f :: k -> *) (a :: k). Backwards f a -> f a
forwards ((i -> a -> Backwards (StateT s Identity) b)
-> t a -> Backwards (StateT s Identity) (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse (\i
i a
c -> StateT s Identity b -> Backwards (StateT s Identity) b
forall k (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards ((s -> (b, s)) -> StateT s Identity b
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
Lazy.state (\s
s -> (s, b) -> (b, s)
forall a b. (a, b) -> (b, a)
swap (i -> s -> a -> (s, b)
f i
i s
s a
c)))) t a
a)) s
s0)
{-# INLINE imapAccumR #-}

-- | Generalizes 'Data.Traversable.mapAccumL' to add access to the index.
--
-- 'imapAccumLOf' accumulates state from left to right.
--
-- @
-- 'Control.Lens.Traversal.mapAccumLOf' ≡ 'imapAccumL' '.' 'const'
-- @
imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumL :: (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumL i -> s -> a -> (s, b)
f s
s0 t a
a = (t b, s) -> (s, t b)
forall a b. (a, b) -> (b, a)
swap (State s (t b) -> s -> (t b, s)
forall s a. State s a -> s -> (a, s)
Lazy.runState ((i -> a -> StateT s Identity b) -> t a -> State s (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse (\i
i a
c -> (s -> (b, s)) -> StateT s Identity b
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
Lazy.state (\s
s -> (s, b) -> (b, s)
forall a b. (a, b) -> (b, a)
swap (i -> s -> a -> (s, b)
f i
i s
s a
c))) t a
a) s
s0)
{-# INLINE imapAccumL #-}