indexed-traversable-0.1.1: FunctorWithIndex, FoldableWithIndex, TraversableWithIndex
Safe HaskellSafe
LanguageHaskell2010

Data.Functor.WithIndex

Synopsis

Indexed Functors

class Functor f => FunctorWithIndex i f | f -> i where Source #

A Functor with an additional index.

Instances must satisfy a modified form of the Functor laws:

imap f . imap g ≡ imap (\i -> f i . g i)
imap (\_ a -> a) ≡ id

Minimal complete definition

Nothing

Methods

imap :: (i -> a -> b) -> f a -> f b Source #

Map with access to the index.

default imap :: TraversableWithIndex i f => (i -> a -> b) -> f a -> f b Source #

Instances

Instances details
FunctorWithIndex Int [] Source #

The position in the list is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> [a] -> [b] Source #

FunctorWithIndex Int ZipList Source #

Same instance as for [].

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> ZipList a -> ZipList b Source #

FunctorWithIndex Int NonEmpty Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> NonEmpty a -> NonEmpty b Source #

FunctorWithIndex Int IntMap Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> IntMap a -> IntMap b Source #

FunctorWithIndex Int Seq Source #

The position in the Seq is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b Source #

FunctorWithIndex () Maybe Source # 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Maybe a -> Maybe b Source #

FunctorWithIndex () Par1 Source # 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Par1 a -> Par1 b Source #

FunctorWithIndex () Identity Source # 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Identity a -> Identity b Source #

FunctorWithIndex k (Map k) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (k -> a -> b) -> Map k a -> Map k b Source #

Ix i => FunctorWithIndex i (Array i) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Array i a -> Array i b Source #

FunctorWithIndex k ((,) k) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (k -> a -> b) -> (k, a) -> (k, b) Source #

FunctorWithIndex Void (V1 :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> V1 a -> V1 b Source #

FunctorWithIndex Void (U1 :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> U1 a -> U1 b Source #

FunctorWithIndex Void (Proxy :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Proxy a -> Proxy b Source #

FunctorWithIndex i f => FunctorWithIndex i (Rec1 f) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Rec1 f a -> Rec1 f b Source #

FunctorWithIndex i f => FunctorWithIndex i (Reverse f) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Reverse f a -> Reverse f b Source #

FunctorWithIndex i f => FunctorWithIndex i (Backwards f) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Backwards f a -> Backwards f b Source #

FunctorWithIndex i m => FunctorWithIndex i (IdentityT m) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> IdentityT m a -> IdentityT m b Source #

FunctorWithIndex Void (Const e :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Const e a -> Const e b Source #

FunctorWithIndex Void (Constant e :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Constant e a -> Constant e b Source #

FunctorWithIndex r ((->) r :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (r -> a -> b) -> (r -> a) -> r -> b Source #

FunctorWithIndex Void (K1 i c :: Type -> Type) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> K1 i c a -> K1 i c b Source #

FunctorWithIndex [Int] Tree Source # 
Instance details

Defined in WithIndex

Methods

imap :: ([Int] -> a -> b) -> Tree a -> Tree b Source #

FunctorWithIndex i m => FunctorWithIndex (e, i) (ReaderT e m) Source # 
Instance details

Defined in WithIndex

Methods

imap :: ((e, i) -> a -> b) -> ReaderT e m a -> ReaderT e m b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :+: g) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :*: g) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Product f g) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> Product f g a -> Product f g b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Sum f g) Source # 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> Sum f g a -> Sum f g b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (f :.: g) Source # 
Instance details

Defined in WithIndex

Methods

imap :: ((i, j) -> a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (Compose f g) Source # 
Instance details

Defined in WithIndex

Methods

imap :: ((i, j) -> a -> b) -> Compose f g a -> Compose f g b Source #