{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Traversable.WithIndex (
TraversableWithIndex(..),
ifor,
imapM,
iforM,
imapAccumR,
imapAccumL,
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
import CoerceCompat
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
ifor :: forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
t a -> (i -> a -> f b) -> f (t b)
ifor = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse
{-# INLINE ifor #-}
imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
imapM :: forall i (t :: * -> *) (m :: * -> *) a b.
(TraversableWithIndex i t, Monad m) =>
(i -> a -> m b) -> t a -> m (t b)
imapM i -> a -> m b
f = forall (m :: * -> *) a. WrappedMonad m a -> m a
unwrapMonad forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse (forall (m :: * -> *) a. m a -> WrappedMonad m a
WrapMonad forall b c i a.
Coercible b c =>
(b -> c) -> (i -> a -> b) -> i -> a -> c
#.. i -> a -> m b
f)
{-# INLINE imapM #-}
iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)
iforM :: forall i (t :: * -> *) (m :: * -> *) a b.
(TraversableWithIndex i t, Monad m) =>
t a -> (i -> a -> m b) -> m (t b)
iforM = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall i (t :: * -> *) (m :: * -> *) a b.
(TraversableWithIndex i t, Monad m) =>
(i -> a -> m b) -> t a -> m (t b)
imapM
{-# INLINE iforM #-}
imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumR :: forall i (t :: * -> *) s a b.
TraversableWithIndex i t =>
(i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumR i -> s -> a -> (s, b)
f s
s0 t a
a = forall a b. (a, b) -> (b, a)
swap (forall s a. State s a -> s -> (a, s)
Lazy.runState (forall {k} (f :: k -> *) (a :: k). Backwards f a -> f a
forwards (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 -> forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
Lazy.state (\s
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 #-}
imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumL :: forall i (t :: * -> *) s a b.
TraversableWithIndex i t =>
(i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
imapAccumL i -> s -> a -> (s, b)
f s
s0 t a
a = forall a b. (a, b) -> (b, a)
swap (forall s a. State s a -> s -> (a, s)
Lazy.runState (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 -> forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
Lazy.state (\s
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 #-}