Data.Key
Contents
- type family Key f
- class Functor f => Keyed f  where- mapWithKey :: (Key f -> a -> b) -> f a -> f b
 
- (<#$>) :: Keyed f => (Key f -> a -> b) -> f a -> f b
- keyed :: Keyed f => f a -> f (Key f, a)
- class Functor f => Zip f where
- class (Keyed f, Zip f) => ZipWithKey f  where- zipWithKey :: (Key f -> a -> b -> c) -> f a -> f b -> f c
- zapWithKey :: f (Key f -> a -> b) -> f a -> f b
 
- class Lookup f => Indexable f where
- (!) :: Indexable f => f a -> Key f -> a
- class Lookup f where
- lookupDefault :: Indexable f => Key f -> f a -> Maybe a
- class Functor f => Adjustable f where
- class Foldable t => FoldableWithKey t  where- toKeyedList :: t a -> [(Key t, a)]
- foldMapWithKey :: Monoid m => (Key t -> a -> m) -> t a -> m
- foldrWithKey :: (Key t -> a -> b -> b) -> b -> t a -> b
- foldlWithKey :: (b -> Key t -> a -> b) -> b -> t a -> b
 
- foldrWithKey' :: FoldableWithKey t => (Key t -> a -> b -> b) -> b -> t a -> b
- foldlWithKey' :: FoldableWithKey t => (b -> Key t -> a -> b) -> b -> t a -> b
- foldrWithKeyM :: (FoldableWithKey t, Monad m) => (Key t -> a -> b -> m b) -> b -> t a -> m b
- foldlWithKeyM :: (FoldableWithKey t, Monad m) => (b -> Key t -> a -> m b) -> b -> t a -> m b
- traverseWithKey_ :: (FoldableWithKey t, Applicative f) => (Key t -> a -> f b) -> t a -> f ()
- forWithKey_ :: (FoldableWithKey t, Applicative f) => t a -> (Key t -> a -> f b) -> f ()
- mapWithKeyM_ :: (FoldableWithKey t, Monad m) => (Key t -> a -> m b) -> t a -> m ()
- forWithKeyM_ :: (FoldableWithKey t, Monad m) => t a -> (Key t -> a -> m b) -> m ()
- concatMapWithKey :: FoldableWithKey t => (Key t -> a -> [b]) -> t a -> [b]
- anyWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Bool
- allWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Bool
- findWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Maybe a
- class (Foldable1 t, FoldableWithKey t) => FoldableWithKey1 t  where- foldMapWithKey1 :: Semigroup m => (Key t -> a -> m) -> t a -> m
 
- traverseWithKey1_ :: (FoldableWithKey1 t, Apply f) => (Key t -> a -> f b) -> t a -> f ()
- forWithKey1_ :: (FoldableWithKey1 t, Apply f) => t a -> (Key t -> a -> f b) -> f ()
- foldMapWithKeyDefault1 :: (FoldableWithKey1 t, Monoid m) => (Key t -> a -> m) -> t a -> m
- class (Keyed t, FoldableWithKey t, Traversable t) => TraversableWithKey t  where- traverseWithKey :: Applicative f => (Key t -> a -> f b) -> t a -> f (t b)
- mapWithKeyM :: Monad m => (Key t -> a -> m b) -> t a -> m (t b)
 
- forWithKey :: (TraversableWithKey t, Applicative f) => t a -> (Key t -> a -> f b) -> f (t b)
- forWithKeyM :: (TraversableWithKey t, Monad m) => t a -> (Key t -> a -> m b) -> m (t b)
- mapAccumWithKeyL :: TraversableWithKey t => (Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumWithKeyR :: TraversableWithKey t => (Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapWithKeyDefault :: TraversableWithKey t => (Key t -> a -> b) -> t a -> t b
- foldMapWithKeyDefault :: (TraversableWithKey t, Monoid m) => (Key t -> a -> m) -> t a -> m
- class (Traversable1 t, FoldableWithKey1 t, TraversableWithKey t) => TraversableWithKey1 t  where- traverseWithKey1 :: Apply f => (Key t -> a -> f b) -> t a -> f (t b)
 
- foldMapWithKey1Default :: (TraversableWithKey1 t, Semigroup m) => (Key t -> a -> m) -> t a -> m
- module Data.Foldable
- module Data.Traversable
- module Data.Semigroup
- module Data.Semigroup.Foldable
- module Data.Semigroup.Traversable
Keys
Keyed functors
class Functor f => Keyed f whereSource
Methods
mapWithKey :: (Key f -> a -> b) -> f a -> f bSource
Instances
| Keyed [] | |
| Keyed Identity | |
| Keyed Seq | |
| Keyed IntMap | |
| 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) | 
Zippable functors
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
Instances
| ZipWithKey [] | |
| ZipWithKey Identity | |
| ZipWithKey Seq | |
| ZipWithKey IntMap | |
| ZipWithKey ((->) a) | |
| ZipWithKey m => ZipWithKey (IdentityT m) | |
| Ord k => ZipWithKey (Map k) | |
| ZipWithKey f => ZipWithKey (Cofree f) | |
| ZipWithKey w => ZipWithKey (TracedT s w) | |
| ZipWithKey m => ZipWithKey (ReaderT e m) | |
| (ZipWithKey f, ZipWithKey g) => ZipWithKey (Compose f g) | |
| (ZipWithKey f, ZipWithKey g) => ZipWithKey (Product f g) | 
Indexable functors
class Lookup f => Indexable f whereSource
Instances
| Indexable [] | |
| Indexable Identity | |
| Indexable Seq | |
| Indexable IntMap | |
| Indexable ((->) a) | |
| Ix i => Indexable (Array i) | |
| Indexable m => Indexable (IdentityT m) | |
| Ord k => Indexable (Map k) | |
| Indexable f => Indexable (Cofree f) | |
| Indexable w => Indexable (TracedT s w) | |
| (Indexable f, Indexable g) => Indexable (Coproduct f g) | |
| Indexable m => Indexable (ReaderT e m) | |
| (Indexable f, Indexable g) => Indexable (Compose f g) | |
| (Indexable f, Indexable g) => Indexable (Product f g) | 
Safe Lookup
Instances
| Lookup [] | |
| Lookup Identity | |
| Lookup Seq | |
| Lookup IntMap | |
| 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
Instances
| Adjustable [] | |
| Adjustable Identity | |
| Adjustable Seq | |
| Adjustable IntMap | |
| Ix i => Adjustable (Array i) | |
| Ord k => Adjustable (Map k) | |
| Adjustable f => Adjustable (Free f) | |
| Adjustable f => Adjustable (Cofree f) | |
| (Adjustable f, Adjustable g) => Adjustable (Coproduct f g) | |
| (Adjustable f, Adjustable g) => Adjustable (Product f g) | 
FoldableWithKey
class Foldable t => FoldableWithKey t whereSource
Methods
toKeyedList :: t a -> [(Key t, a)]Source
foldMapWithKey :: Monoid m => (Key t -> a -> m) -> t a -> mSource
foldrWithKey :: (Key t -> a -> b -> b) -> b -> t a -> bSource
foldlWithKey :: (b -> Key t -> a -> b) -> b -> t a -> bSource
Instances
| FoldableWithKey [] | |
| FoldableWithKey Identity | |
| FoldableWithKey Seq | |
| FoldableWithKey IntMap | |
| Ix i => FoldableWithKey (Array i) | |
| FoldableWithKey m => FoldableWithKey (IdentityT m) | |
| FoldableWithKey (Map k) | |
| FoldableWithKey f => FoldableWithKey (Free f) | |
| FoldableWithKey f => FoldableWithKey (Cofree f) | |
| (FoldableWithKey f, FoldableWithKey m) => FoldableWithKey (Compose f m) | |
| (FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (Product f g) | 
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
class (Foldable1 t, FoldableWithKey t) => FoldableWithKey1 t whereSource
Methods
foldMapWithKey1 :: Semigroup m => (Key t -> a -> m) -> t a -> mSource
Instances
| FoldableWithKey1 Identity | |
| FoldableWithKey1 m => FoldableWithKey1 (IdentityT m) | |
| FoldableWithKey1 f => FoldableWithKey1 (Free f) | |
| FoldableWithKey1 f => FoldableWithKey1 (Cofree f) | |
| (FoldableWithKey1 f, FoldableWithKey1 m) => FoldableWithKey1 (Compose f m) | |
| (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Product f g) | 
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
class (Keyed t, FoldableWithKey t, Traversable t) => TraversableWithKey t whereSource
Methods
traverseWithKey :: Applicative f => (Key t -> a -> f b) -> t a -> f (t b)Source
mapWithKeyM :: Monad m => (Key t -> a -> m b) -> t a -> m (t b)Source
Instances
| TraversableWithKey [] | |
| TraversableWithKey Identity | |
| TraversableWithKey Seq | |
| TraversableWithKey IntMap | |
| Ix i => TraversableWithKey (Array i) | |
| TraversableWithKey m => TraversableWithKey (IdentityT m) | |
| TraversableWithKey (Map k) | |
| TraversableWithKey f => TraversableWithKey (Free f) | |
| TraversableWithKey f => TraversableWithKey (Cofree f) | |
| (TraversableWithKey f, TraversableWithKey m) => TraversableWithKey (Compose f m) | |
| (TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (Product f g) | 
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 Data.Foldable.foldMapWithKey
 in a FoldableWithKey instance.
TraverableWithKey1
class (Traversable1 t, FoldableWithKey1 t, TraversableWithKey t) => TraversableWithKey1 t whereSource
Methods
traverseWithKey1 :: Apply f => (Key t -> a -> f b) -> t a -> f (t b)Source
Instances
| TraversableWithKey1 Identity | |
| TraversableWithKey1 m => TraversableWithKey1 (IdentityT m) | |
| TraversableWithKey1 f => TraversableWithKey1 (Free f) | |
| TraversableWithKey1 f => TraversableWithKey1 (Cofree f) | |
| (TraversableWithKey1 f, TraversableWithKey1 m) => TraversableWithKey1 (Compose f m) | |
| (TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (Product f g) | 
foldMapWithKey1Default :: (TraversableWithKey1 t, Semigroup m) => (Key t -> a -> m) -> t a -> mSource
module Data.Foldable
module Data.Traversable
module Data.Semigroup
module Data.Semigroup.Foldable
module Data.Semigroup.Traversable