Safe Haskell | Trustworthy |
---|---|
Language | Haskell98 |
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
Keys
Instances
type Key [] = Int | |
type Key Maybe = () | |
type Key Identity = () | |
type Key IntMap = Int | |
type Key Tree = Seq Int | |
type Key Seq = Int | |
type Key NonEmpty = Int | |
type Key ((->) a) = a | |
type Key ((,) k) = k | |
type Key (Array i) = i | |
type Key (IdentityT m) = Key m | |
type Key (Map k) = k | |
type Key (Cofree f) = Seq (Key f) | |
type Key (Free f) = Seq (Key f) | |
type Key (HashMap k) = k | |
type Key (Coproduct f g) = (Key f, Key g) | |
type Key (TracedT s w) = (s, Key w) | |
type Key (ReaderT e m) = (e, Key m) | |
type Key (Compose f g) = (Key f, Key g) | |
type Key (Product f g) = Either (Key f) (Key g) |
Keyed functors
class Functor f => Keyed f where Source
Methods
mapWithKey :: (Key f -> a -> b) -> f a -> f b Source
Instances
Keyed [] | |
Keyed Maybe | |
Keyed Identity | |
Keyed IntMap | |
Keyed Tree | |
Keyed Seq | |
Keyed NonEmpty | |
Keyed ((->) a) | |
Keyed ((,) k) | |
Ix i => Keyed (Array i) | |
Keyed m => Keyed (IdentityT m) | |
Keyed (Map k) | |
Keyed f => Keyed (Cofree f) | |
Keyed f => Keyed (Free f) | |
Keyed (HashMap k) | |
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
class Functor f => Zip f where Source
Minimal complete definition
Nothing
Instances
Zip [] | |
Zip Maybe | |
Zip Identity | |
Zip IntMap | |
Zip Tree | |
Zip Seq | |
Zip NonEmpty | |
Zip ((->) a) | |
Zip m => Zip (IdentityT m) | |
Ord k => Zip (Map k) | |
Zip f => Zip (Cofree f) | |
(Eq k, Hashable k) => Zip (HashMap k) | |
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 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
ZipWithKey [] | |
ZipWithKey Maybe | |
ZipWithKey Identity | |
ZipWithKey IntMap | |
ZipWithKey Tree | |
ZipWithKey Seq | |
ZipWithKey NonEmpty | |
ZipWithKey ((->) a) | |
ZipWithKey m => ZipWithKey (IdentityT m) | |
Ord k => ZipWithKey (Map k) | |
ZipWithKey f => ZipWithKey (Cofree f) | |
(Eq k, Hashable k) => ZipWithKey (HashMap k) | |
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 where Source
Instances
Indexable [] | |
Indexable Maybe | |
Indexable Identity | |
Indexable IntMap | |
Indexable Tree | |
Indexable Seq | |
Indexable NonEmpty | |
Indexable ((->) a) | |
Ix i => Indexable (Array i) | |
Indexable m => Indexable (IdentityT m) | |
Ord k => Indexable (Map k) | |
Indexable f => Indexable (Cofree f) | |
(Eq k, Hashable k) => Indexable (HashMap k) | |
(Indexable f, Indexable g) => Indexable (Coproduct f g) | |
Indexable w => Indexable (TracedT s w) | |
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 Maybe | |
Lookup Identity | |
Lookup IntMap | |
Lookup Tree | |
Lookup Seq | |
Lookup NonEmpty | |
Lookup ((->) a) | |
Ix i => Lookup (Array i) | |
Lookup m => Lookup (IdentityT m) | |
Ord k => Lookup (Map k) | |
Lookup f => Lookup (Cofree f) | |
Lookup f => Lookup (Free f) | |
(Eq k, Hashable k) => Lookup (HashMap k) | |
(Lookup f, Lookup g) => Lookup (Coproduct f g) | |
Lookup w => Lookup (TracedT s w) | |
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 a Source
Adjustable
class Functor f => Adjustable f where Source
Minimal complete definition
Instances
Adjustable [] | |
Adjustable Identity | |
Adjustable IntMap | |
Adjustable Tree | |
Adjustable Seq | |
Adjustable NonEmpty | |
Ix i => Adjustable (Array i) | |
Ord k => Adjustable (Map k) | |
Adjustable f => Adjustable (Cofree f) | |
Adjustable f => Adjustable (Free f) | |
(Adjustable f, Adjustable g) => Adjustable (Coproduct f g) | |
(Adjustable f, Adjustable g) => Adjustable (Product f g) |
FoldableWithKey
class Foldable t => FoldableWithKey t where Source
Minimal complete definition
Nothing
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
FoldableWithKey [] | |
FoldableWithKey Maybe | |
FoldableWithKey Identity | |
FoldableWithKey IntMap | |
FoldableWithKey Tree | |
FoldableWithKey Seq | |
FoldableWithKey NonEmpty | |
FoldableWithKey ((,) k) | |
Ix i => FoldableWithKey (Array i) | |
FoldableWithKey m => FoldableWithKey (IdentityT m) | |
FoldableWithKey (Map k) | |
FoldableWithKey f => FoldableWithKey (Cofree f) | |
FoldableWithKey f => FoldableWithKey (Free f) | |
FoldableWithKey (HashMap k) | |
(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 -> 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 | |
FoldableWithKey1 Tree | |
FoldableWithKey1 NonEmpty | |
FoldableWithKey1 ((,) k) | |
FoldableWithKey1 m => FoldableWithKey1 (IdentityT m) | |
FoldableWithKey1 f => FoldableWithKey1 (Cofree f) | |
FoldableWithKey1 f => FoldableWithKey1 (Free 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 -> 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