keys-2.2: Keyed functors and containers

Safe HaskellSafe-Infered

Data.Key

Contents

Synopsis

Keys

type family Key f Source

Keyed functors

class Functor f => Keyed f whereSource

Methods

mapWithKey :: (Key f -> a -> b) -> f a -> f bSource

Instances

Keyed [] 
Keyed Identity 
Keyed Tree 
Keyed Seq 
Keyed IntMap 
Keyed NonEmpty 
Keyed ((->) a) 
Ix i => Keyed (Array i) 
Keyed m => Keyed (IdentityT m) 
Keyed (Map k) 
Keyed f => Keyed (Free f) 
Keyed f => Keyed (Cofree f) 
Keyed w => Keyed (TracedT s w) 
Keyed m => Keyed (ReaderT e m) 
(Keyed f, Keyed g) => Keyed (Compose f g) 
(Keyed f, Keyed g) => Keyed (Product f g) 

(<#$>) :: Keyed f => (Key f -> a -> b) -> f a -> f bSource

keyed :: Keyed f => f a -> f (Key f, a)Source

Zippable functors

class Functor f => Zip f whereSource

Methods

zipWith :: (a -> b -> c) -> f a -> f b -> f cSource

zip :: f a -> f b -> f (a, b)Source

zap :: f (a -> b) -> f a -> f bSource

Instances

Zip [] 
Zip Identity 
Zip Tree 
Zip Seq 
Zip IntMap 
Zip NonEmpty 
Zip ((->) a) 
Zip m => Zip (IdentityT m) 
Ord k => Zip (Map k) 
Zip f => Zip (Cofree f) 
Zip w => Zip (TracedT s w) 
Zip m => Zip (ReaderT e m) 
(Zip f, Zip g) => Zip (Compose f g) 
(Zip f, Zip g) => Zip (Product f g) 

Zipping keyed functors

class (Keyed f, Zip f) => ZipWithKey f whereSource

Methods

zipWithKey :: (Key f -> a -> b -> c) -> f a -> f b -> f cSource

zapWithKey :: f (Key f -> a -> b) -> f a -> f bSource

Indexable functors

(!) :: Indexable f => f a -> Key f -> aSource

Safe Lookup

class Lookup f whereSource

Methods

lookup :: Key f -> f a -> Maybe aSource

Instances

Lookup [] 
Lookup Identity 
Lookup Tree 
Lookup Seq 
Lookup IntMap 
Lookup NonEmpty 
Lookup ((->) a) 
Ix i => Lookup (Array i) 
Lookup m => Lookup (IdentityT m) 
Ord k => Lookup (Map k) 
Lookup f => Lookup (Free f) 
Lookup f => Lookup (Cofree f) 
Lookup w => Lookup (TracedT s w) 
(Lookup f, Lookup g) => Lookup (Coproduct f g) 
Lookup m => Lookup (ReaderT e m) 
(Lookup f, Lookup g) => Lookup (Compose f g) 
(Lookup f, Lookup g) => Lookup (Product f g) 

lookupDefault :: Indexable f => Key f -> f a -> Maybe aSource

Adjustable

class Functor f => Adjustable f whereSource

Methods

adjust :: (a -> a) -> Key f -> f a -> f aSource

replace :: Key f -> a -> f a -> f aSource

FoldableWithKey

foldrWithKey' :: FoldableWithKey t => (Key t -> a -> b -> b) -> b -> t a -> bSource

foldlWithKey' :: FoldableWithKey t => (b -> Key t -> a -> b) -> b -> t a -> bSource

foldrWithKeyM :: (FoldableWithKey t, Monad m) => (Key t -> a -> b -> m b) -> b -> t a -> m bSource

foldlWithKeyM :: (FoldableWithKey t, Monad m) => (b -> Key t -> a -> m b) -> b -> t a -> m bSource

traverseWithKey_ :: (FoldableWithKey t, Applicative f) => (Key t -> a -> f b) -> t a -> f ()Source

forWithKey_ :: (FoldableWithKey t, Applicative f) => t a -> (Key t -> a -> f b) -> f ()Source

mapWithKeyM_ :: (FoldableWithKey t, Monad m) => (Key t -> a -> m b) -> t a -> m ()Source

forWithKeyM_ :: (FoldableWithKey t, Monad m) => t a -> (Key t -> a -> m b) -> m ()Source

concatMapWithKey :: FoldableWithKey t => (Key t -> a -> [b]) -> t a -> [b]Source

anyWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> BoolSource

allWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> BoolSource

findWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Maybe aSource

FoldableWithKey1

traverseWithKey1_ :: (FoldableWithKey1 t, Apply f) => (Key t -> a -> f b) -> t a -> f ()Source

forWithKey1_ :: (FoldableWithKey1 t, Apply f) => t a -> (Key t -> a -> f b) -> f ()Source

foldMapWithKeyDefault1 :: (FoldableWithKey1 t, Monoid m) => (Key t -> a -> m) -> t a -> mSource

TraversableWithKey

forWithKey :: (TraversableWithKey t, Applicative f) => t a -> (Key t -> a -> f b) -> f (t b)Source

forWithKeyM :: (TraversableWithKey t, Monad m) => t a -> (Key t -> a -> m b) -> m (t b)Source

mapAccumWithKeyL :: TraversableWithKey t => (Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)Source

The mapAccumWithKeyL function behaves like a combination of mapWithKey and foldlWithKey; it applies a function to each element of a structure, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new structure.

mapAccumWithKeyR :: TraversableWithKey t => (Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)Source

The mapAccumWithKeyR function behaves like a combination of mapWithKey and foldrWithKey; it applies a function to each element of a structure, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new structure.

mapWithKeyDefault :: TraversableWithKey t => (Key t -> a -> b) -> t a -> t bSource

foldMapWithKeyDefault :: (TraversableWithKey t, Monoid m) => (Key t -> a -> m) -> t a -> mSource

This function may be used as a value for foldMapWithKey in a FoldableWithKey instance.

TraverableWithKey1

foldMapWithKey1Default :: (TraversableWithKey1 t, Semigroup m) => (Key t -> a -> m) -> t a -> mSource