keys-3.11: Keyed functors and containers

Safe HaskellSafe
LanguageHaskell98

Data.Key

Contents

Synopsis

Keys

type family Key f Source

Instances

type Key [] = Int Source 
type Key Identity = () Source 
type Key Maybe = () Source 
type Key IntMap = Int Source 
type Key Tree = Seq Int Source 
type Key Seq = Int Source 
type Key NonEmpty = Int Source 
type Key ((->) a) = a Source 
type Key ((,) k) = k Source 
type Key (Array i) = i Source 
type Key (IdentityT m) = Key m Source 
type Key (Map k) = k Source 
type Key (Cofree f) = Seq (Key f) Source 
type Key (Free f) = Seq (Key f) Source 
type Key (HashMap k) = k Source 
type Key (TracedT s w) = (s, Key w) Source 
type Key (ReaderT e m) = (e, Key m) Source 
type Key (Compose f g) = (Key f, Key g) Source 
type Key (Sum f g) = (Key f, Key g) Source 
type Key (Product f g) = Either (Key f) (Key g) Source 

Keyed functors

class Functor f => Keyed f where Source

Methods

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

(<#$>) :: Keyed f => (Key f -> a -> b) -> f a -> f b infixl 4 Source

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

Zippable functors

class Functor f => Zip f where Source

Minimal complete definition

Nothing

Methods

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

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

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

Instances

Zip [] Source 
Zip Identity Source 
Zip Maybe Source 
Zip IntMap Source 
Zip Tree Source 
Zip Seq Source 
Zip NonEmpty Source 
Zip ((->) a) Source 
Zip m => Zip (IdentityT m) Source 
Ord k => Zip (Map k) Source 
Zip f => Zip (Cofree f) Source 
(Eq k, Hashable k) => Zip (HashMap k) Source 
Zip w => Zip (TracedT s w) Source 
Zip m => Zip (ReaderT e m) Source 
(Zip f, Zip g) => Zip (Compose f g) Source 
(Zip f, Zip g) => Zip (Product f g) 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

Indexable functors

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

Safe Lookup

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

Adjustable

FoldableWithKey

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

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

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

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