| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Data.Key
Synopsis
- 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
 
Keys
type family Key (f :: * -> *) Source #
Instances
Keyed functors
class Functor f => Keyed f where Source #
Methods
mapWithKey :: (Key f -> a -> b) -> f a -> f b Source #
Instances
Zippable functors
class Functor f => Zip f where Source #
Laws:
fmapfst(zipu u) = ufmapsnd(zipu u) = uzip(fmapfstu) (fmapsndu) = uzip(flip(,)) x y =zipy x
Instances
| Zip ZipList Source # | |
| Zip Identity Source # | |
| Zip NonEmpty Source # | |
| Zip Par1 Source # | |
| Zip IntMap Source # | |
| Zip Seq Source # | |
| Zip Tree Source # | |
| Zip Maybe Source # | |
| Zip List Source # | |
| Zip (Proxy :: Type -> Type) Source # | |
| Zip (U1 :: Type -> Type) Source # | |
| Zip (V1 :: Type -> Type) Source # | |
| Ord k => Zip (Map k) Source # | |
| Zip f => Zip (Cofree f) Source # | |
| (Eq k, Hashable k) => Zip (HashMap k) Source # | |
| Zip f => Zip (Rec1 f) Source # | |
| Zip w => Zip (TracedT s w) Source # | |
| Zip (Tagged a) Source # | |
| Zip m => Zip (IdentityT m) Source # | |
| Zip m => Zip (ReaderT e m) Source # | |
| (Zip f, Zip g) => Zip (Product f g) Source # | |
| (Zip f, Zip g) => Zip (f :*: g) Source # | |
| Zip ((->) a) Source # | |
| (Zip f, Zip g) => Zip (Compose f g) Source # | |
| (Zip f, Zip g) => Zip (g :.: f) Source # | |
| Zip f => Zip (M1 i c f) Source # | |
Zipping keyed functors
class (Keyed f, Zip f) => ZipWithKey f where Source #
Minimal complete definition
Nothing
Methods
zipWithKey :: (Key f -> a -> b -> c) -> f a -> f b -> f c Source #
zapWithKey :: f (Key f -> a -> b) -> f a -> f b Source #
Instances
Indexable functors
class Lookup f => Indexable f where Source #
Instances
Safe Lookup
Instances
Adjustable
class Functor f => Adjustable f where Source #
Minimal complete definition
Instances
FoldableWithKey
class Foldable t => FoldableWithKey t where Source #
Minimal complete definition
Methods
toKeyedList :: t a -> [(Key t, a)] Source #
foldMapWithKey :: Monoid m => (Key t -> a -> m) -> t a -> m Source #
foldrWithKey :: (Key t -> a -> b -> b) -> b -> t a -> b Source #
foldlWithKey :: (b -> Key t -> a -> b) -> b -> t a -> b Source #
Instances
foldrWithKey' :: FoldableWithKey t => (Key t -> a -> b -> b) -> b -> t a -> b Source #
foldlWithKey' :: FoldableWithKey t => (b -> Key t -> a -> b) -> b -> t a -> b Source #
foldrWithKeyM :: (FoldableWithKey t, Monad m) => (Key t -> a -> b -> m b) -> b -> t a -> m b Source #
foldlWithKeyM :: (FoldableWithKey t, Monad m) => (b -> Key t -> a -> m b) -> b -> t a -> m b Source #
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 -> Bool Source #
allWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Bool Source #
findWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Maybe a Source #
FoldableWithKey1
class (Foldable1 t, FoldableWithKey t) => FoldableWithKey1 t where Source #
Methods
foldMapWithKey1 :: Semigroup m => (Key t -> a -> m) -> t a -> m Source #
Instances
| FoldableWithKey1 Identity Source # | |
| FoldableWithKey1 NonEmpty Source # | |
| FoldableWithKey1 Par1 Source # | |
| FoldableWithKey1 Tree Source # | |
| FoldableWithKey1 (V1 :: Type -> Type) Source # | |
| FoldableWithKey1 f => FoldableWithKey1 (Cofree f) Source # | |
| FoldableWithKey1 f => FoldableWithKey1 (Free f) Source # | |
| FoldableWithKey1 ((,) k) Source # | |
| FoldableWithKey1 f => FoldableWithKey1 (Rec1 f) Source # | |
| FoldableWithKey1 (Tagged a) Source # | |
| FoldableWithKey1 m => FoldableWithKey1 (IdentityT m) Source # | |
| (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Product f g) Source # | |
| (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Sum f g) Source # | |
| (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (f :*: g) Source # | |
| (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (f :+: g) Source # | |
| (FoldableWithKey1 f, FoldableWithKey1 m) => FoldableWithKey1 (Compose f m) Source # | |
| FoldableWithKey1 f => FoldableWithKey1 (M1 i c f) Source # | |
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 -> m Source #
TraversableWithKey
class (Keyed t, FoldableWithKey t, Traversable t) => TraversableWithKey t where Source #
Minimal complete definition
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
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 b Source #
foldMapWithKeyDefault :: (TraversableWithKey t, Monoid m) => (Key t -> a -> m) -> t a -> m Source #
This function may be used as a value for foldMapWithKey
 in a FoldableWithKey instance.
TraversableWithKey1
class (Traversable1 t, FoldableWithKey1 t, TraversableWithKey t) => TraversableWithKey1 t where Source #
Methods
traverseWithKey1 :: Apply f => (Key t -> a -> f b) -> t a -> f (t b) Source #
Instances
foldMapWithKey1Default :: (TraversableWithKey1 t, Semigroup m) => (Key t -> a -> m) -> t a -> m Source #