keys-3.12: Keyed functors and containers

Safe HaskellSafe
LanguageHaskell2010

Data.Key

Contents

Synopsis

Keys

type family Key (f :: * -> *) Source #

Instances

type Key [] Source # 
type Key [] = Int
type Key Maybe Source # 
type Key Maybe = ()
type Key Par1 Source # 
type Key Par1 = ()
type Key NonEmpty Source # 
type Key ZipList Source # 
type Key ZipList = Int
type Key Identity Source # 
type Key Identity = ()
type Key IntMap Source # 
type Key IntMap = Int
type Key Tree Source # 
type Key Tree = Seq Int
type Key Seq Source # 
type Key Seq = Int
type Key (V1 *) Source # 
type Key (V1 *) = Void
type Key (U1 *) Source # 
type Key (U1 *) = Void
type Key ((,) k) Source # 
type Key ((,) k) = k
type Key (Array i) Source # 
type Key (Array i) = i
type Key (Proxy *) Source # 
type Key (Proxy *) = Void
type Key (Map k) Source # 
type Key (Map k) = k
type Key (Cofree f) Source # 
type Key (Cofree f) = Seq (Key f)
type Key (Free f) Source # 
type Key (Free f) = Seq (Key f)
type Key (HashMap k) Source # 
type Key (HashMap k) = k
type Key (Rec1 * f) Source # 
type Key (Rec1 * f) = Key f
type Key (TracedT s w) Source # 
type Key (TracedT s w) = (s, Key w)
type Key (IdentityT * m) Source # 
type Key (IdentityT * m) = Key m
type Key (Tagged * a) Source # 
type Key (Tagged * a) = ()
type Key ((->) LiftedRep LiftedRep a) Source # 
type Key ((->) LiftedRep LiftedRep a) = a
type Key (K1 * i c) Source # 
type Key (K1 * i c) = Void
type Key ((:+:) * f g) Source # 
type Key ((:+:) * f g) = Either (Key f) (Key g)
type Key ((:*:) * f g) Source # 
type Key ((:*:) * f g) = Either (Key f) (Key g)
type Key (Product * f g) Source # 
type Key (Product * f g) = Either (Key f) (Key g)
type Key (Sum * f g) Source # 
type Key (Sum * f g) = Either (Key f) (Key g)
type Key (ReaderT * e m) Source # 
type Key (ReaderT * e m) = (e, Key m)
type Key (M1 * i c f) Source # 
type Key (M1 * i c f) = Key f
type Key ((:.:) * * g f) Source # 
type Key ((:.:) * * g f) = (Key g, Key f)
type Key (Compose * * f g) Source # 
type Key (Compose * * f g) = (Key f, Key g)

Keyed functors

class Functor f => Keyed f where Source #

Minimal complete definition

mapWithKey

Methods

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

Instances

Keyed [] Source # 

Methods

mapWithKey :: (Key [] -> a -> b) -> [a] -> [b] Source #

Keyed Maybe Source # 

Methods

mapWithKey :: (Key Maybe -> a -> b) -> Maybe a -> Maybe b Source #

Keyed Par1 Source # 

Methods

mapWithKey :: (Key Par1 -> a -> b) -> Par1 a -> Par1 b Source #

Keyed NonEmpty Source # 

Methods

mapWithKey :: (Key NonEmpty -> a -> b) -> NonEmpty a -> NonEmpty b Source #

Keyed ZipList Source # 

Methods

mapWithKey :: (Key ZipList -> a -> b) -> ZipList a -> ZipList b Source #

Keyed Identity Source # 

Methods

mapWithKey :: (Key Identity -> a -> b) -> Identity a -> Identity b Source #

Keyed IntMap Source # 

Methods

mapWithKey :: (Key IntMap -> a -> b) -> IntMap a -> IntMap b Source #

Keyed Tree Source # 

Methods

mapWithKey :: (Key Tree -> a -> b) -> Tree a -> Tree b Source #

Keyed Seq Source # 

Methods

mapWithKey :: (Key Seq -> a -> b) -> Seq a -> Seq b Source #

Keyed (V1 *) Source # 

Methods

mapWithKey :: (Key (V1 *) -> a -> b) -> V1 * a -> V1 * b Source #

Keyed (U1 *) Source # 

Methods

mapWithKey :: (Key (U1 *) -> a -> b) -> U1 * a -> U1 * b Source #

Keyed ((,) k) Source # 

Methods

mapWithKey :: (Key ((,) k) -> a -> b) -> (k, a) -> (k, b) Source #

Ix i => Keyed (Array i) Source # 

Methods

mapWithKey :: (Key (Array i) -> a -> b) -> Array i a -> Array i b Source #

Keyed (Proxy *) Source # 

Methods

mapWithKey :: (Key (Proxy *) -> a -> b) -> Proxy * a -> Proxy * b Source #

Keyed (Map k) Source # 

Methods

mapWithKey :: (Key (Map k) -> a -> b) -> Map k a -> Map k b Source #

Keyed f => Keyed (Cofree f) Source # 

Methods

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

Keyed f => Keyed (Free f) Source # 

Methods

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

Keyed (HashMap k) Source # 

Methods

mapWithKey :: (Key (HashMap k) -> a -> b) -> HashMap k a -> HashMap k b Source #

Keyed f => Keyed (Rec1 * f) Source # 

Methods

mapWithKey :: (Key (Rec1 * f) -> a -> b) -> Rec1 * f a -> Rec1 * f b Source #

Keyed w => Keyed (TracedT s w) Source # 

Methods

mapWithKey :: (Key (TracedT s w) -> a -> b) -> TracedT s w a -> TracedT s w b Source #

Keyed m => Keyed (IdentityT * m) Source # 

Methods

mapWithKey :: (Key (IdentityT * m) -> a -> b) -> IdentityT * m a -> IdentityT * m b Source #

Keyed (Tagged * a) Source # 

Methods

mapWithKey :: (Key (Tagged * a) -> a -> b) -> Tagged * a a -> Tagged * a b Source #

Keyed ((->) LiftedRep LiftedRep a) Source # 

Methods

mapWithKey :: (Key ((LiftedRep -> LiftedRep) a) -> a -> b) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b Source #

Keyed (K1 * i c) Source # 

Methods

mapWithKey :: (Key (K1 * i c) -> a -> b) -> K1 * i c a -> K1 * i c b Source #

(Keyed g, Keyed f) => Keyed ((:+:) * f g) Source # 

Methods

mapWithKey :: (Key ((* :+: f) g) -> a -> b) -> (* :+: f) g a -> (* :+: f) g b Source #

(Keyed g, Keyed f) => Keyed ((:*:) * f g) Source # 

Methods

mapWithKey :: (Key ((* :*: f) g) -> a -> b) -> (* :*: f) g a -> (* :*: f) g b Source #

(Keyed f, Keyed g) => Keyed (Product * f g) Source # 

Methods

mapWithKey :: (Key (Product * f g) -> a -> b) -> Product * f g a -> Product * f g b Source #

(Keyed f, Keyed g) => Keyed (Sum * f g) Source # 

Methods

mapWithKey :: (Key (Sum * f g) -> a -> b) -> Sum * f g a -> Sum * f g b Source #

Keyed m => Keyed (ReaderT * e m) Source # 

Methods

mapWithKey :: (Key (ReaderT * e m) -> a -> b) -> ReaderT * e m a -> ReaderT * e m b Source #

Keyed f => Keyed (M1 * i c f) Source # 

Methods

mapWithKey :: (Key (M1 * i c f) -> a -> b) -> M1 * i c f a -> M1 * i c f b Source #

(Keyed g, Keyed f) => Keyed ((:.:) * * g f) Source # 

Methods

mapWithKey :: (Key ((* :.: *) g f) -> a -> b) -> (* :.: *) g f a -> (* :.: *) g f b Source #

(Keyed f, Keyed g) => Keyed (Compose * * f g) Source # 

Methods

mapWithKey :: (Key (Compose * * f g) -> a -> b) -> Compose * * f g a -> Compose * * f g 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 #

Laws:

fmap fst (zip u u) = u
fmap snd (zip u u) = u
zip (fmap fst u) (fmap snd u) = u
zip (flip (,)) x y = zip y x

Minimal complete definition

zipWith | zip

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 # 

Methods

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

zip :: [a] -> [b] -> [(a, b)] Source #

zap :: [a -> b] -> [a] -> [b] Source #

Zip Maybe Source # 

Methods

zipWith :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

zip :: Maybe a -> Maybe b -> Maybe (a, b) Source #

zap :: Maybe (a -> b) -> Maybe a -> Maybe b Source #

Zip Par1 Source # 

Methods

zipWith :: (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c Source #

zip :: Par1 a -> Par1 b -> Par1 (a, b) Source #

zap :: Par1 (a -> b) -> Par1 a -> Par1 b Source #

Zip NonEmpty Source # 

Methods

zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) Source #

zap :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b Source #

Zip ZipList Source # 

Methods

zipWith :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

zip :: ZipList a -> ZipList b -> ZipList (a, b) Source #

zap :: ZipList (a -> b) -> ZipList a -> ZipList b Source #

Zip Identity Source # 

Methods

zipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

zip :: Identity a -> Identity b -> Identity (a, b) Source #

zap :: Identity (a -> b) -> Identity a -> Identity b Source #

Zip IntMap Source # 

Methods

zipWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c Source #

zip :: IntMap a -> IntMap b -> IntMap (a, b) Source #

zap :: IntMap (a -> b) -> IntMap a -> IntMap b Source #

Zip Tree Source # 

Methods

zipWith :: (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

zip :: Tree a -> Tree b -> Tree (a, b) Source #

zap :: Tree (a -> b) -> Tree a -> Tree b Source #

Zip Seq Source # 

Methods

zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

zip :: Seq a -> Seq b -> Seq (a, b) Source #

zap :: Seq (a -> b) -> Seq a -> Seq b Source #

Zip (V1 *) Source # 

Methods

zipWith :: (a -> b -> c) -> V1 * a -> V1 * b -> V1 * c Source #

zip :: V1 * a -> V1 * b -> V1 * (a, b) Source #

zap :: V1 * (a -> b) -> V1 * a -> V1 * b Source #

Zip (U1 *) Source # 

Methods

zipWith :: (a -> b -> c) -> U1 * a -> U1 * b -> U1 * c Source #

zip :: U1 * a -> U1 * b -> U1 * (a, b) Source #

zap :: U1 * (a -> b) -> U1 * a -> U1 * b Source #

Zip (Proxy *) Source # 

Methods

zipWith :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c Source #

zip :: Proxy * a -> Proxy * b -> Proxy * (a, b) Source #

zap :: Proxy * (a -> b) -> Proxy * a -> Proxy * b Source #

Ord k => Zip (Map k) Source # 

Methods

zipWith :: (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

zip :: Map k a -> Map k b -> Map k (a, b) Source #

zap :: Map k (a -> b) -> Map k a -> Map k b Source #

Zip f => Zip (Cofree f) Source # 

Methods

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

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

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

(Eq k, Hashable k) => Zip (HashMap k) Source # 

Methods

zipWith :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c Source #

zip :: HashMap k a -> HashMap k b -> HashMap k (a, b) Source #

zap :: HashMap k (a -> b) -> HashMap k a -> HashMap k b Source #

Zip f => Zip (Rec1 * f) Source # 

Methods

zipWith :: (a -> b -> c) -> Rec1 * f a -> Rec1 * f b -> Rec1 * f c Source #

zip :: Rec1 * f a -> Rec1 * f b -> Rec1 * f (a, b) Source #

zap :: Rec1 * f (a -> b) -> Rec1 * f a -> Rec1 * f b Source #

Zip w => Zip (TracedT s w) Source # 

Methods

zipWith :: (a -> b -> c) -> TracedT s w a -> TracedT s w b -> TracedT s w c Source #

zip :: TracedT s w a -> TracedT s w b -> TracedT s w (a, b) Source #

zap :: TracedT s w (a -> b) -> TracedT s w a -> TracedT s w b Source #

Zip m => Zip (IdentityT * m) Source # 

Methods

zipWith :: (a -> b -> c) -> IdentityT * m a -> IdentityT * m b -> IdentityT * m c Source #

zip :: IdentityT * m a -> IdentityT * m b -> IdentityT * m (a, b) Source #

zap :: IdentityT * m (a -> b) -> IdentityT * m a -> IdentityT * m b Source #

Zip (Tagged * a) Source # 

Methods

zipWith :: (a -> b -> c) -> Tagged * a a -> Tagged * a b -> Tagged * a c Source #

zip :: Tagged * a a -> Tagged * a b -> Tagged * a (a, b) Source #

zap :: Tagged * a (a -> b) -> Tagged * a a -> Tagged * a b Source #

Zip ((->) LiftedRep LiftedRep a) Source # 

Methods

zipWith :: (a -> b -> c) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a c Source #

zip :: (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a (a, b) Source #

zap :: (LiftedRep -> LiftedRep) a (a -> b) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b Source #

(Zip f, Zip g) => Zip ((:*:) * f g) Source # 

Methods

zipWith :: (a -> b -> c) -> (* :*: f) g a -> (* :*: f) g b -> (* :*: f) g c Source #

zip :: (* :*: f) g a -> (* :*: f) g b -> (* :*: f) g (a, b) Source #

zap :: (* :*: f) g (a -> b) -> (* :*: f) g a -> (* :*: f) g b Source #

(Zip f, Zip g) => Zip (Product * f g) Source # 

Methods

zipWith :: (a -> b -> c) -> Product * f g a -> Product * f g b -> Product * f g c Source #

zip :: Product * f g a -> Product * f g b -> Product * f g (a, b) Source #

zap :: Product * f g (a -> b) -> Product * f g a -> Product * f g b Source #

Zip m => Zip (ReaderT * e m) Source # 

Methods

zipWith :: (a -> b -> c) -> ReaderT * e m a -> ReaderT * e m b -> ReaderT * e m c Source #

zip :: ReaderT * e m a -> ReaderT * e m b -> ReaderT * e m (a, b) Source #

zap :: ReaderT * e m (a -> b) -> ReaderT * e m a -> ReaderT * e m b Source #

Zip f => Zip (M1 * i c f) Source # 

Methods

zipWith :: (a -> b -> c) -> M1 * i c f a -> M1 * i c f b -> M1 * i c f c Source #

zip :: M1 * i c f a -> M1 * i c f b -> M1 * i c f (a, b) Source #

zap :: M1 * i c f (a -> b) -> M1 * i c f a -> M1 * i c f b Source #

(Zip f, Zip g) => Zip ((:.:) * * g f) Source # 

Methods

zipWith :: (a -> b -> c) -> (* :.: *) g f a -> (* :.: *) g f b -> (* :.: *) g f c Source #

zip :: (* :.: *) g f a -> (* :.: *) g f b -> (* :.: *) g f (a, b) Source #

zap :: (* :.: *) g f (a -> b) -> (* :.: *) g f a -> (* :.: *) g f b Source #

(Zip f, Zip g) => Zip (Compose * * f g) Source # 

Methods

zipWith :: (a -> b -> c) -> Compose * * f g a -> Compose * * f g b -> Compose * * f g c Source #

zip :: Compose * * f g a -> Compose * * f g b -> Compose * * f g (a, b) Source #

zap :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b Source #

Zipping keyed functors

class (Keyed f, Zip f) => ZipWithKey f where Source #

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 [] Source # 

Methods

zipWithKey :: (Key [] -> a -> b -> c) -> [a] -> [b] -> [c] Source #

zapWithKey :: [Key [] -> a -> b] -> [a] -> [b] Source #

ZipWithKey Maybe Source # 

Methods

zipWithKey :: (Key Maybe -> a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

zapWithKey :: Maybe (Key Maybe -> a -> b) -> Maybe a -> Maybe b Source #

ZipWithKey Par1 Source # 

Methods

zipWithKey :: (Key Par1 -> a -> b -> c) -> Par1 a -> Par1 b -> Par1 c Source #

zapWithKey :: Par1 (Key Par1 -> a -> b) -> Par1 a -> Par1 b Source #

ZipWithKey NonEmpty Source # 

Methods

zipWithKey :: (Key NonEmpty -> a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

zapWithKey :: NonEmpty (Key NonEmpty -> a -> b) -> NonEmpty a -> NonEmpty b Source #

ZipWithKey ZipList Source # 

Methods

zipWithKey :: (Key ZipList -> a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

zapWithKey :: ZipList (Key ZipList -> a -> b) -> ZipList a -> ZipList b Source #

ZipWithKey Identity Source # 

Methods

zipWithKey :: (Key Identity -> a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

zapWithKey :: Identity (Key Identity -> a -> b) -> Identity a -> Identity b Source #

ZipWithKey IntMap Source # 

Methods

zipWithKey :: (Key IntMap -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c Source #

zapWithKey :: IntMap (Key IntMap -> a -> b) -> IntMap a -> IntMap b Source #

ZipWithKey Tree Source # 

Methods

zipWithKey :: (Key Tree -> a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

zapWithKey :: Tree (Key Tree -> a -> b) -> Tree a -> Tree b Source #

ZipWithKey Seq Source # 

Methods

zipWithKey :: (Key Seq -> a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

zapWithKey :: Seq (Key Seq -> a -> b) -> Seq a -> Seq b Source #

ZipWithKey (V1 *) Source # 

Methods

zipWithKey :: (Key (V1 *) -> a -> b -> c) -> V1 * a -> V1 * b -> V1 * c Source #

zapWithKey :: V1 * (Key (V1 *) -> a -> b) -> V1 * a -> V1 * b Source #

ZipWithKey (U1 *) Source # 

Methods

zipWithKey :: (Key (U1 *) -> a -> b -> c) -> U1 * a -> U1 * b -> U1 * c Source #

zapWithKey :: U1 * (Key (U1 *) -> a -> b) -> U1 * a -> U1 * b Source #

ZipWithKey (Proxy *) Source # 

Methods

zipWithKey :: (Key (Proxy *) -> a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c Source #

zapWithKey :: Proxy * (Key (Proxy *) -> a -> b) -> Proxy * a -> Proxy * b Source #

Ord k => ZipWithKey (Map k) Source # 

Methods

zipWithKey :: (Key (Map k) -> a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

zapWithKey :: Map k (Key (Map k) -> a -> b) -> Map k a -> Map k b Source #

ZipWithKey f => ZipWithKey (Cofree f) Source # 

Methods

zipWithKey :: (Key (Cofree f) -> a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c Source #

zapWithKey :: Cofree f (Key (Cofree f) -> a -> b) -> Cofree f a -> Cofree f b Source #

(Eq k, Hashable k) => ZipWithKey (HashMap k) Source # 

Methods

zipWithKey :: (Key (HashMap k) -> a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c Source #

zapWithKey :: HashMap k (Key (HashMap k) -> a -> b) -> HashMap k a -> HashMap k b Source #

ZipWithKey f => ZipWithKey (Rec1 * f) Source # 

Methods

zipWithKey :: (Key (Rec1 * f) -> a -> b -> c) -> Rec1 * f a -> Rec1 * f b -> Rec1 * f c Source #

zapWithKey :: Rec1 * f (Key (Rec1 * f) -> a -> b) -> Rec1 * f a -> Rec1 * f b Source #

ZipWithKey w => ZipWithKey (TracedT s w) Source # 

Methods

zipWithKey :: (Key (TracedT s w) -> a -> b -> c) -> TracedT s w a -> TracedT s w b -> TracedT s w c Source #

zapWithKey :: TracedT s w (Key (TracedT s w) -> a -> b) -> TracedT s w a -> TracedT s w b Source #

ZipWithKey m => ZipWithKey (IdentityT * m) Source # 

Methods

zipWithKey :: (Key (IdentityT * m) -> a -> b -> c) -> IdentityT * m a -> IdentityT * m b -> IdentityT * m c Source #

zapWithKey :: IdentityT * m (Key (IdentityT * m) -> a -> b) -> IdentityT * m a -> IdentityT * m b Source #

ZipWithKey (Tagged * a) Source # 

Methods

zipWithKey :: (Key (Tagged * a) -> a -> b -> c) -> Tagged * a a -> Tagged * a b -> Tagged * a c Source #

zapWithKey :: Tagged * a (Key (Tagged * a) -> a -> b) -> Tagged * a a -> Tagged * a b Source #

ZipWithKey ((->) LiftedRep LiftedRep a) Source # 

Methods

zipWithKey :: (Key ((LiftedRep -> LiftedRep) a) -> a -> b -> c) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a c Source #

zapWithKey :: (LiftedRep -> LiftedRep) a (Key ((LiftedRep -> LiftedRep) a) -> a -> b) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b Source #

(ZipWithKey f, ZipWithKey g) => ZipWithKey ((:*:) * f g) Source # 

Methods

zipWithKey :: (Key ((* :*: f) g) -> a -> b -> c) -> (* :*: f) g a -> (* :*: f) g b -> (* :*: f) g c Source #

zapWithKey :: (* :*: f) g (Key ((* :*: f) g) -> a -> b) -> (* :*: f) g a -> (* :*: f) g b Source #

(ZipWithKey f, ZipWithKey g) => ZipWithKey (Product * f g) Source # 

Methods

zipWithKey :: (Key (Product * f g) -> a -> b -> c) -> Product * f g a -> Product * f g b -> Product * f g c Source #

zapWithKey :: Product * f g (Key (Product * f g) -> a -> b) -> Product * f g a -> Product * f g b Source #

ZipWithKey m => ZipWithKey (ReaderT * e m) Source # 

Methods

zipWithKey :: (Key (ReaderT * e m) -> a -> b -> c) -> ReaderT * e m a -> ReaderT * e m b -> ReaderT * e m c Source #

zapWithKey :: ReaderT * e m (Key (ReaderT * e m) -> a -> b) -> ReaderT * e m a -> ReaderT * e m b Source #

ZipWithKey f => ZipWithKey (M1 * i c f) Source # 

Methods

zipWithKey :: (Key (M1 * i c f) -> a -> b -> c) -> M1 * i c f a -> M1 * i c f b -> M1 * i c f c Source #

zapWithKey :: M1 * i c f (Key (M1 * i c f) -> a -> b) -> M1 * i c f a -> M1 * i c f b Source #

(ZipWithKey f, ZipWithKey g) => ZipWithKey ((:.:) * * g f) Source # 

Methods

zipWithKey :: (Key ((* :.: *) g f) -> a -> b -> c) -> (* :.: *) g f a -> (* :.: *) g f b -> (* :.: *) g f c Source #

zapWithKey :: (* :.: *) g f (Key ((* :.: *) g f) -> a -> b) -> (* :.: *) g f a -> (* :.: *) g f b Source #

(ZipWithKey f, ZipWithKey g) => ZipWithKey (Compose * * f g) Source # 

Methods

zipWithKey :: (Key (Compose * * f g) -> a -> b -> c) -> Compose * * f g a -> Compose * * f g b -> Compose * * f g c Source #

zapWithKey :: Compose * * f g (Key (Compose * * f g) -> a -> b) -> Compose * * f g a -> Compose * * f g b Source #

Indexable functors

class Lookup f => Indexable f where Source #

Minimal complete definition

index

Methods

index :: f a -> Key f -> a Source #

Instances

Indexable [] Source # 

Methods

index :: [a] -> Key [] -> a Source #

Indexable Maybe Source # 

Methods

index :: Maybe a -> Key Maybe -> a Source #

Indexable Par1 Source # 

Methods

index :: Par1 a -> Key Par1 -> a Source #

Indexable NonEmpty Source # 

Methods

index :: NonEmpty a -> Key NonEmpty -> a Source #

Indexable ZipList Source # 

Methods

index :: ZipList a -> Key ZipList -> a Source #

Indexable Identity Source # 

Methods

index :: Identity a -> Key Identity -> a Source #

Indexable IntMap Source # 

Methods

index :: IntMap a -> Key IntMap -> a Source #

Indexable Tree Source # 

Methods

index :: Tree a -> Key Tree -> a Source #

Indexable Seq Source # 

Methods

index :: Seq a -> Key Seq -> a Source #

Indexable (U1 *) Source # 

Methods

index :: U1 * a -> Key (U1 *) -> a Source #

Ix i => Indexable (Array i) Source # 

Methods

index :: Array i a -> Key (Array i) -> a Source #

Indexable (Proxy *) Source # 

Methods

index :: Proxy * a -> Key (Proxy *) -> a Source #

Ord k => Indexable (Map k) Source # 

Methods

index :: Map k a -> Key (Map k) -> a Source #

Indexable f => Indexable (Cofree f) Source # 

Methods

index :: Cofree f a -> Key (Cofree f) -> a Source #

(Eq k, Hashable k) => Indexable (HashMap k) Source # 

Methods

index :: HashMap k a -> Key (HashMap k) -> a Source #

Indexable f => Indexable (Rec1 * f) Source # 

Methods

index :: Rec1 * f a -> Key (Rec1 * f) -> a Source #

Indexable w => Indexable (TracedT s w) Source # 

Methods

index :: TracedT s w a -> Key (TracedT s w) -> a Source #

Indexable m => Indexable (IdentityT * m) Source # 

Methods

index :: IdentityT * m a -> Key (IdentityT * m) -> a Source #

Indexable (Tagged * a) Source # 

Methods

index :: Tagged * a a -> Key (Tagged * a) -> a Source #

Indexable ((->) LiftedRep LiftedRep a) Source # 

Methods

index :: (LiftedRep -> LiftedRep) a a -> Key ((LiftedRep -> LiftedRep) a) -> a Source #

Indexable (K1 * i c) Source # 

Methods

index :: K1 * i c a -> Key (K1 * i c) -> a Source #

(Indexable g, Indexable f) => Indexable ((:*:) * f g) Source # 

Methods

index :: (* :*: f) g a -> Key ((* :*: f) g) -> a Source #

(Indexable f, Indexable g) => Indexable (Product * f g) Source # 

Methods

index :: Product * f g a -> Key (Product * f g) -> a Source #

(Indexable f, Indexable g) => Indexable (Sum * f g) Source # 

Methods

index :: Sum * f g a -> Key (Sum * f g) -> a Source #

Indexable m => Indexable (ReaderT * e m) Source # 

Methods

index :: ReaderT * e m a -> Key (ReaderT * e m) -> a Source #

Indexable f => Indexable (M1 * i c f) Source # 

Methods

index :: M1 * i c f a -> Key (M1 * i c f) -> a Source #

(Indexable g, Indexable f) => Indexable ((:.:) * * g f) Source # 

Methods

index :: (* :.: *) g f a -> Key ((* :.: *) g f) -> a Source #

(Indexable f, Indexable g) => Indexable (Compose * * f g) Source # 

Methods

index :: Compose * * f g a -> Key (Compose * * f g) -> a Source #

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

Safe Lookup

class Lookup f where Source #

Minimal complete definition

lookup

Methods

lookup :: Key f -> f a -> Maybe a Source #

Instances

Lookup [] Source # 

Methods

lookup :: Key [] -> [a] -> Maybe a Source #

Lookup Maybe Source # 

Methods

lookup :: Key Maybe -> Maybe a -> Maybe a Source #

Lookup Par1 Source # 

Methods

lookup :: Key Par1 -> Par1 a -> Maybe a Source #

Lookup NonEmpty Source # 

Methods

lookup :: Key NonEmpty -> NonEmpty a -> Maybe a Source #

Lookup ZipList Source # 

Methods

lookup :: Key ZipList -> ZipList a -> Maybe a Source #

Lookup Identity Source # 

Methods

lookup :: Key Identity -> Identity a -> Maybe a Source #

Lookup IntMap Source # 

Methods

lookup :: Key IntMap -> IntMap a -> Maybe a Source #

Lookup Tree Source # 

Methods

lookup :: Key Tree -> Tree a -> Maybe a Source #

Lookup Seq Source # 

Methods

lookup :: Key Seq -> Seq a -> Maybe a Source #

Lookup (U1 *) Source # 

Methods

lookup :: Key (U1 *) -> U1 * a -> Maybe a Source #

Ix i => Lookup (Array i) Source # 

Methods

lookup :: Key (Array i) -> Array i a -> Maybe a Source #

Lookup (Proxy *) Source # 

Methods

lookup :: Key (Proxy *) -> Proxy * a -> Maybe a Source #

Ord k => Lookup (Map k) Source # 

Methods

lookup :: Key (Map k) -> Map k a -> Maybe a Source #

Lookup f => Lookup (Cofree f) Source # 

Methods

lookup :: Key (Cofree f) -> Cofree f a -> Maybe a Source #

Lookup f => Lookup (Free f) Source # 

Methods

lookup :: Key (Free f) -> Free f a -> Maybe a Source #

(Eq k, Hashable k) => Lookup (HashMap k) Source # 

Methods

lookup :: Key (HashMap k) -> HashMap k a -> Maybe a Source #

Lookup f => Lookup (Rec1 * f) Source # 

Methods

lookup :: Key (Rec1 * f) -> Rec1 * f a -> Maybe a Source #

Lookup w => Lookup (TracedT s w) Source # 

Methods

lookup :: Key (TracedT s w) -> TracedT s w a -> Maybe a Source #

Lookup m => Lookup (IdentityT * m) Source # 

Methods

lookup :: Key (IdentityT * m) -> IdentityT * m a -> Maybe a Source #

Lookup (Tagged * a) Source # 

Methods

lookup :: Key (Tagged * a) -> Tagged * a a -> Maybe a Source #

Lookup ((->) LiftedRep LiftedRep a) Source # 

Methods

lookup :: Key ((LiftedRep -> LiftedRep) a) -> (LiftedRep -> LiftedRep) a a -> Maybe a Source #

Lookup (K1 * i c) Source # 

Methods

lookup :: Key (K1 * i c) -> K1 * i c a -> Maybe a Source #

(Indexable g, Indexable f) => Lookup ((:*:) * f g) Source # 

Methods

lookup :: Key ((* :*: f) g) -> (* :*: f) g a -> Maybe a Source #

(Lookup f, Lookup g) => Lookup (Product * f g) Source # 

Methods

lookup :: Key (Product * f g) -> Product * f g a -> Maybe a Source #

(Lookup f, Lookup g) => Lookup (Sum * f g) Source # 

Methods

lookup :: Key (Sum * f g) -> Sum * f g a -> Maybe a Source #

Lookup m => Lookup (ReaderT * e m) Source # 

Methods

lookup :: Key (ReaderT * e m) -> ReaderT * e m a -> Maybe a Source #

Lookup f => Lookup (M1 * i c f) Source # 

Methods

lookup :: Key (M1 * i c f) -> M1 * i c f a -> Maybe a Source #

(Indexable g, Indexable f) => Lookup ((:.:) * * g f) Source # 

Methods

lookup :: Key ((* :.: *) g f) -> (* :.: *) g f a -> Maybe a Source #

(Lookup f, Lookup g) => Lookup (Compose * * f g) Source # 

Methods

lookup :: Key (Compose * * f g) -> Compose * * f g a -> Maybe a Source #

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

Adjustable

class Functor f => Adjustable f where Source #

Minimal complete definition

adjust

Methods

adjust :: (a -> a) -> Key f -> f a -> f a Source #

replace :: Key f -> a -> f a -> f a Source #

Instances

Adjustable [] Source # 

Methods

adjust :: (a -> a) -> Key [] -> [a] -> [a] Source #

replace :: Key [] -> a -> [a] -> [a] Source #

Adjustable Par1 Source # 

Methods

adjust :: (a -> a) -> Key Par1 -> Par1 a -> Par1 a Source #

replace :: Key Par1 -> a -> Par1 a -> Par1 a Source #

Adjustable NonEmpty Source # 

Methods

adjust :: (a -> a) -> Key NonEmpty -> NonEmpty a -> NonEmpty a Source #

replace :: Key NonEmpty -> a -> NonEmpty a -> NonEmpty a Source #

Adjustable ZipList Source # 

Methods

adjust :: (a -> a) -> Key ZipList -> ZipList a -> ZipList a Source #

replace :: Key ZipList -> a -> ZipList a -> ZipList a Source #

Adjustable Identity Source # 

Methods

adjust :: (a -> a) -> Key Identity -> Identity a -> Identity a Source #

replace :: Key Identity -> a -> Identity a -> Identity a Source #

Adjustable IntMap Source # 

Methods

adjust :: (a -> a) -> Key IntMap -> IntMap a -> IntMap a Source #

replace :: Key IntMap -> a -> IntMap a -> IntMap a Source #

Adjustable Tree Source # 

Methods

adjust :: (a -> a) -> Key Tree -> Tree a -> Tree a Source #

replace :: Key Tree -> a -> Tree a -> Tree a Source #

Adjustable Seq Source # 

Methods

adjust :: (a -> a) -> Key Seq -> Seq a -> Seq a Source #

replace :: Key Seq -> a -> Seq a -> Seq a Source #

Adjustable (U1 *) Source # 

Methods

adjust :: (a -> a) -> Key (U1 *) -> U1 * a -> U1 * a Source #

replace :: Key (U1 *) -> a -> U1 * a -> U1 * a Source #

Ix i => Adjustable (Array i) Source # 

Methods

adjust :: (a -> a) -> Key (Array i) -> Array i a -> Array i a Source #

replace :: Key (Array i) -> a -> Array i a -> Array i a Source #

Adjustable (Proxy *) Source # 

Methods

adjust :: (a -> a) -> Key (Proxy *) -> Proxy * a -> Proxy * a Source #

replace :: Key (Proxy *) -> a -> Proxy * a -> Proxy * a Source #

Ord k => Adjustable (Map k) Source # 

Methods

adjust :: (a -> a) -> Key (Map k) -> Map k a -> Map k a Source #

replace :: Key (Map k) -> a -> Map k a -> Map k a Source #

Adjustable f => Adjustable (Cofree f) Source # 

Methods

adjust :: (a -> a) -> Key (Cofree f) -> Cofree f a -> Cofree f a Source #

replace :: Key (Cofree f) -> a -> Cofree f a -> Cofree f a Source #

Adjustable f => Adjustable (Free f) Source # 

Methods

adjust :: (a -> a) -> Key (Free f) -> Free f a -> Free f a Source #

replace :: Key (Free f) -> a -> Free f a -> Free f a Source #

Adjustable f => Adjustable (Rec1 * f) Source # 

Methods

adjust :: (a -> a) -> Key (Rec1 * f) -> Rec1 * f a -> Rec1 * f a Source #

replace :: Key (Rec1 * f) -> a -> Rec1 * f a -> Rec1 * f a Source #

Adjustable (Tagged * a) Source # 

Methods

adjust :: (a -> a) -> Key (Tagged * a) -> Tagged * a a -> Tagged * a a Source #

replace :: Key (Tagged * a) -> a -> Tagged * a a -> Tagged * a a Source #

Adjustable (K1 * i c) Source # 

Methods

adjust :: (a -> a) -> Key (K1 * i c) -> K1 * i c a -> K1 * i c a Source #

replace :: Key (K1 * i c) -> a -> K1 * i c a -> K1 * i c a Source #

(Adjustable f, Adjustable g) => Adjustable ((:+:) * f g) Source # 

Methods

adjust :: (a -> a) -> Key ((* :+: f) g) -> (* :+: f) g a -> (* :+: f) g a Source #

replace :: Key ((* :+: f) g) -> a -> (* :+: f) g a -> (* :+: f) g a Source #

(Adjustable f, Adjustable g) => Adjustable ((:*:) * f g) Source # 

Methods

adjust :: (a -> a) -> Key ((* :*: f) g) -> (* :*: f) g a -> (* :*: f) g a Source #

replace :: Key ((* :*: f) g) -> a -> (* :*: f) g a -> (* :*: f) g a Source #

(Adjustable f, Adjustable g) => Adjustable (Product * f g) Source # 

Methods

adjust :: (a -> a) -> Key (Product * f g) -> Product * f g a -> Product * f g a Source #

replace :: Key (Product * f g) -> a -> Product * f g a -> Product * f g a Source #

(Adjustable f, Adjustable g) => Adjustable (Sum * f g) Source # 

Methods

adjust :: (a -> a) -> Key (Sum * f g) -> Sum * f g a -> Sum * f g a Source #

replace :: Key (Sum * f g) -> a -> Sum * f g a -> Sum * f g a Source #

Adjustable f => Adjustable (M1 * i c f) Source # 

Methods

adjust :: (a -> a) -> Key (M1 * i c f) -> M1 * i c f a -> M1 * i c f a Source #

replace :: Key (M1 * i c f) -> a -> M1 * i c f a -> M1 * i c f a Source #

(Adjustable f, Adjustable g) => Adjustable ((:.:) * * g f) Source # 

Methods

adjust :: (a -> a) -> Key ((* :.: *) g f) -> (* :.: *) g f a -> (* :.: *) g f a Source #

replace :: Key ((* :.: *) g f) -> a -> (* :.: *) g f a -> (* :.: *) g f a Source #

FoldableWithKey

class Foldable t => FoldableWithKey t where Source #

Minimal complete definition

foldMapWithKey | foldrWithKey

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 [] Source # 

Methods

toKeyedList :: [a] -> [(Key [], a)] Source #

foldMapWithKey :: Monoid m => (Key [] -> a -> m) -> [a] -> m Source #

foldrWithKey :: (Key [] -> a -> b -> b) -> b -> [a] -> b Source #

foldlWithKey :: (b -> Key [] -> a -> b) -> b -> [a] -> b Source #

FoldableWithKey Maybe Source # 

Methods

toKeyedList :: Maybe a -> [(Key Maybe, a)] Source #

foldMapWithKey :: Monoid m => (Key Maybe -> a -> m) -> Maybe a -> m Source #

foldrWithKey :: (Key Maybe -> a -> b -> b) -> b -> Maybe a -> b Source #

foldlWithKey :: (b -> Key Maybe -> a -> b) -> b -> Maybe a -> b Source #

FoldableWithKey Par1 Source # 

Methods

toKeyedList :: Par1 a -> [(Key Par1, a)] Source #

foldMapWithKey :: Monoid m => (Key Par1 -> a -> m) -> Par1 a -> m Source #

foldrWithKey :: (Key Par1 -> a -> b -> b) -> b -> Par1 a -> b Source #

foldlWithKey :: (b -> Key Par1 -> a -> b) -> b -> Par1 a -> b Source #

FoldableWithKey NonEmpty Source # 

Methods

toKeyedList :: NonEmpty a -> [(Key NonEmpty, a)] Source #

foldMapWithKey :: Monoid m => (Key NonEmpty -> a -> m) -> NonEmpty a -> m Source #

foldrWithKey :: (Key NonEmpty -> a -> b -> b) -> b -> NonEmpty a -> b Source #

foldlWithKey :: (b -> Key NonEmpty -> a -> b) -> b -> NonEmpty a -> b Source #

FoldableWithKey ZipList Source # 

Methods

toKeyedList :: ZipList a -> [(Key ZipList, a)] Source #

foldMapWithKey :: Monoid m => (Key ZipList -> a -> m) -> ZipList a -> m Source #

foldrWithKey :: (Key ZipList -> a -> b -> b) -> b -> ZipList a -> b Source #

foldlWithKey :: (b -> Key ZipList -> a -> b) -> b -> ZipList a -> b Source #

FoldableWithKey Identity Source # 

Methods

toKeyedList :: Identity a -> [(Key Identity, a)] Source #

foldMapWithKey :: Monoid m => (Key Identity -> a -> m) -> Identity a -> m Source #

foldrWithKey :: (Key Identity -> a -> b -> b) -> b -> Identity a -> b Source #

foldlWithKey :: (b -> Key Identity -> a -> b) -> b -> Identity a -> b Source #

FoldableWithKey IntMap Source # 

Methods

toKeyedList :: IntMap a -> [(Key IntMap, a)] Source #

foldMapWithKey :: Monoid m => (Key IntMap -> a -> m) -> IntMap a -> m Source #

foldrWithKey :: (Key IntMap -> a -> b -> b) -> b -> IntMap a -> b Source #

foldlWithKey :: (b -> Key IntMap -> a -> b) -> b -> IntMap a -> b Source #

FoldableWithKey Tree Source # 

Methods

toKeyedList :: Tree a -> [(Key Tree, a)] Source #

foldMapWithKey :: Monoid m => (Key Tree -> a -> m) -> Tree a -> m Source #

foldrWithKey :: (Key Tree -> a -> b -> b) -> b -> Tree a -> b Source #

foldlWithKey :: (b -> Key Tree -> a -> b) -> b -> Tree a -> b Source #

FoldableWithKey Seq Source # 

Methods

toKeyedList :: Seq a -> [(Key Seq, a)] Source #

foldMapWithKey :: Monoid m => (Key Seq -> a -> m) -> Seq a -> m Source #

foldrWithKey :: (Key Seq -> a -> b -> b) -> b -> Seq a -> b Source #

foldlWithKey :: (b -> Key Seq -> a -> b) -> b -> Seq a -> b Source #

FoldableWithKey (V1 *) Source # 

Methods

toKeyedList :: V1 * a -> [(Key (V1 *), a)] Source #

foldMapWithKey :: Monoid m => (Key (V1 *) -> a -> m) -> V1 * a -> m Source #

foldrWithKey :: (Key (V1 *) -> a -> b -> b) -> b -> V1 * a -> b Source #

foldlWithKey :: (b -> Key (V1 *) -> a -> b) -> b -> V1 * a -> b Source #

FoldableWithKey (U1 *) Source # 

Methods

toKeyedList :: U1 * a -> [(Key (U1 *), a)] Source #

foldMapWithKey :: Monoid m => (Key (U1 *) -> a -> m) -> U1 * a -> m Source #

foldrWithKey :: (Key (U1 *) -> a -> b -> b) -> b -> U1 * a -> b Source #

foldlWithKey :: (b -> Key (U1 *) -> a -> b) -> b -> U1 * a -> b Source #

FoldableWithKey ((,) k) Source # 

Methods

toKeyedList :: (k, a) -> [(Key ((,) k), a)] Source #

foldMapWithKey :: Monoid m => (Key ((,) k) -> a -> m) -> (k, a) -> m Source #

foldrWithKey :: (Key ((,) k) -> a -> b -> b) -> b -> (k, a) -> b Source #

foldlWithKey :: (b -> Key ((,) k) -> a -> b) -> b -> (k, a) -> b Source #

Ix i => FoldableWithKey (Array i) Source # 

Methods

toKeyedList :: Array i a -> [(Key (Array i), a)] Source #

foldMapWithKey :: Monoid m => (Key (Array i) -> a -> m) -> Array i a -> m Source #

foldrWithKey :: (Key (Array i) -> a -> b -> b) -> b -> Array i a -> b Source #

foldlWithKey :: (b -> Key (Array i) -> a -> b) -> b -> Array i a -> b Source #

FoldableWithKey (Proxy *) Source # 

Methods

toKeyedList :: Proxy * a -> [(Key (Proxy *), a)] Source #

foldMapWithKey :: Monoid m => (Key (Proxy *) -> a -> m) -> Proxy * a -> m Source #

foldrWithKey :: (Key (Proxy *) -> a -> b -> b) -> b -> Proxy * a -> b Source #

foldlWithKey :: (b -> Key (Proxy *) -> a -> b) -> b -> Proxy * a -> b Source #

FoldableWithKey (Map k) Source # 

Methods

toKeyedList :: Map k a -> [(Key (Map k), a)] Source #

foldMapWithKey :: Monoid m => (Key (Map k) -> a -> m) -> Map k a -> m Source #

foldrWithKey :: (Key (Map k) -> a -> b -> b) -> b -> Map k a -> b Source #

foldlWithKey :: (b -> Key (Map k) -> a -> b) -> b -> Map k a -> b Source #

FoldableWithKey f => FoldableWithKey (Cofree f) Source # 

Methods

toKeyedList :: Cofree f a -> [(Key (Cofree f), a)] Source #

foldMapWithKey :: Monoid m => (Key (Cofree f) -> a -> m) -> Cofree f a -> m Source #

foldrWithKey :: (Key (Cofree f) -> a -> b -> b) -> b -> Cofree f a -> b Source #

foldlWithKey :: (b -> Key (Cofree f) -> a -> b) -> b -> Cofree f a -> b Source #

FoldableWithKey f => FoldableWithKey (Free f) Source # 

Methods

toKeyedList :: Free f a -> [(Key (Free f), a)] Source #

foldMapWithKey :: Monoid m => (Key (Free f) -> a -> m) -> Free f a -> m Source #

foldrWithKey :: (Key (Free f) -> a -> b -> b) -> b -> Free f a -> b Source #

foldlWithKey :: (b -> Key (Free f) -> a -> b) -> b -> Free f a -> b Source #

FoldableWithKey (HashMap k) Source # 

Methods

toKeyedList :: HashMap k a -> [(Key (HashMap k), a)] Source #

foldMapWithKey :: Monoid m => (Key (HashMap k) -> a -> m) -> HashMap k a -> m Source #

foldrWithKey :: (Key (HashMap k) -> a -> b -> b) -> b -> HashMap k a -> b Source #

foldlWithKey :: (b -> Key (HashMap k) -> a -> b) -> b -> HashMap k a -> b Source #

FoldableWithKey f => FoldableWithKey (Rec1 * f) Source # 

Methods

toKeyedList :: Rec1 * f a -> [(Key (Rec1 * f), a)] Source #

foldMapWithKey :: Monoid m => (Key (Rec1 * f) -> a -> m) -> Rec1 * f a -> m Source #

foldrWithKey :: (Key (Rec1 * f) -> a -> b -> b) -> b -> Rec1 * f a -> b Source #

foldlWithKey :: (b -> Key (Rec1 * f) -> a -> b) -> b -> Rec1 * f a -> b Source #

FoldableWithKey m => FoldableWithKey (IdentityT * m) Source # 

Methods

toKeyedList :: IdentityT * m a -> [(Key (IdentityT * m), a)] Source #

foldMapWithKey :: Monoid m => (Key (IdentityT * m) -> a -> m) -> IdentityT * m a -> m Source #

foldrWithKey :: (Key (IdentityT * m) -> a -> b -> b) -> b -> IdentityT * m a -> b Source #

foldlWithKey :: (b -> Key (IdentityT * m) -> a -> b) -> b -> IdentityT * m a -> b Source #

FoldableWithKey (Tagged * a) Source # 

Methods

toKeyedList :: Tagged * a a -> [(Key (Tagged * a), a)] Source #

foldMapWithKey :: Monoid m => (Key (Tagged * a) -> a -> m) -> Tagged * a a -> m Source #

foldrWithKey :: (Key (Tagged * a) -> a -> b -> b) -> b -> Tagged * a a -> b Source #

foldlWithKey :: (b -> Key (Tagged * a) -> a -> b) -> b -> Tagged * a a -> b Source #

FoldableWithKey (K1 * i c) Source # 

Methods

toKeyedList :: K1 * i c a -> [(Key (K1 * i c), a)] Source #

foldMapWithKey :: Monoid m => (Key (K1 * i c) -> a -> m) -> K1 * i c a -> m Source #

foldrWithKey :: (Key (K1 * i c) -> a -> b -> b) -> b -> K1 * i c a -> b Source #

foldlWithKey :: (b -> Key (K1 * i c) -> a -> b) -> b -> K1 * i c a -> b Source #

(FoldableWithKey f, FoldableWithKey g) => FoldableWithKey ((:+:) * f g) Source # 

Methods

toKeyedList :: (* :+: f) g a -> [(Key ((* :+: f) g), a)] Source #

foldMapWithKey :: Monoid m => (Key ((* :+: f) g) -> a -> m) -> (* :+: f) g a -> m Source #

foldrWithKey :: (Key ((* :+: f) g) -> a -> b -> b) -> b -> (* :+: f) g a -> b Source #

foldlWithKey :: (b -> Key ((* :+: f) g) -> a -> b) -> b -> (* :+: f) g a -> b Source #

(FoldableWithKey f, FoldableWithKey g) => FoldableWithKey ((:*:) * f g) Source # 

Methods

toKeyedList :: (* :*: f) g a -> [(Key ((* :*: f) g), a)] Source #

foldMapWithKey :: Monoid m => (Key ((* :*: f) g) -> a -> m) -> (* :*: f) g a -> m Source #

foldrWithKey :: (Key ((* :*: f) g) -> a -> b -> b) -> b -> (* :*: f) g a -> b Source #

foldlWithKey :: (b -> Key ((* :*: f) g) -> a -> b) -> b -> (* :*: f) g a -> b Source #

(FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (Product * f g) Source # 

Methods

toKeyedList :: Product * f g a -> [(Key (Product * f g), a)] Source #

foldMapWithKey :: Monoid m => (Key (Product * f g) -> a -> m) -> Product * f g a -> m Source #

foldrWithKey :: (Key (Product * f g) -> a -> b -> b) -> b -> Product * f g a -> b Source #

foldlWithKey :: (b -> Key (Product * f g) -> a -> b) -> b -> Product * f g a -> b Source #

(FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (Sum * f g) Source # 

Methods

toKeyedList :: Sum * f g a -> [(Key (Sum * f g), a)] Source #

foldMapWithKey :: Monoid m => (Key (Sum * f g) -> a -> m) -> Sum * f g a -> m Source #

foldrWithKey :: (Key (Sum * f g) -> a -> b -> b) -> b -> Sum * f g a -> b Source #

foldlWithKey :: (b -> Key (Sum * f g) -> a -> b) -> b -> Sum * f g a -> b Source #

FoldableWithKey f => FoldableWithKey (M1 * i c f) Source # 

Methods

toKeyedList :: M1 * i c f a -> [(Key (M1 * i c f), a)] Source #

foldMapWithKey :: Monoid m => (Key (M1 * i c f) -> a -> m) -> M1 * i c f a -> m Source #

foldrWithKey :: (Key (M1 * i c f) -> a -> b -> b) -> b -> M1 * i c f a -> b Source #

foldlWithKey :: (b -> Key (M1 * i c f) -> a -> b) -> b -> M1 * i c f a -> b Source #

(FoldableWithKey f, FoldableWithKey m) => FoldableWithKey (Compose * * f m) Source # 

Methods

toKeyedList :: Compose * * f m a -> [(Key (Compose * * f m), a)] Source #

foldMapWithKey :: Monoid m => (Key (Compose * * f m) -> a -> m) -> Compose * * f m a -> m Source #

foldrWithKey :: (Key (Compose * * f m) -> a -> b -> b) -> b -> Compose * * f m a -> b Source #

foldlWithKey :: (b -> Key (Compose * * f m) -> a -> b) -> b -> Compose * * f m a -> b Source #

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 #

Minimal complete definition

foldMapWithKey1

Methods

foldMapWithKey1 :: Semigroup m => (Key t -> a -> m) -> t a -> m Source #

Instances

FoldableWithKey1 Par1 Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key Par1 -> a -> m) -> Par1 a -> m Source #

FoldableWithKey1 NonEmpty Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key NonEmpty -> a -> m) -> NonEmpty a -> m Source #

FoldableWithKey1 Identity Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key Identity -> a -> m) -> Identity a -> m Source #

FoldableWithKey1 Tree Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key Tree -> a -> m) -> Tree a -> m Source #

FoldableWithKey1 (V1 *) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (V1 *) -> a -> m) -> V1 * a -> m Source #

FoldableWithKey1 ((,) k) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key ((,) k) -> a -> m) -> (k, a) -> m Source #

FoldableWithKey1 f => FoldableWithKey1 (Cofree f) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Cofree f) -> a -> m) -> Cofree f a -> m Source #

FoldableWithKey1 f => FoldableWithKey1 (Free f) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Free f) -> a -> m) -> Free f a -> m Source #

FoldableWithKey1 f => FoldableWithKey1 (Rec1 * f) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Rec1 * f) -> a -> m) -> Rec1 * f a -> m Source #

FoldableWithKey1 m => FoldableWithKey1 (IdentityT * m) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (IdentityT * m) -> a -> m) -> IdentityT * m a -> m Source #

FoldableWithKey1 (Tagged * a) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Tagged * a) -> a -> m) -> Tagged * a a -> m Source #

(FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 ((:+:) * f g) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key ((* :+: f) g) -> a -> m) -> (* :+: f) g a -> m Source #

(FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 ((:*:) * f g) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key ((* :*: f) g) -> a -> m) -> (* :*: f) g a -> m Source #

(FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Product * f g) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Product * f g) -> a -> m) -> Product * f g a -> m Source #

(FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Sum * f g) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Sum * f g) -> a -> m) -> Sum * f g a -> m Source #

FoldableWithKey1 f => FoldableWithKey1 (M1 * i c f) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (M1 * i c f) -> a -> m) -> M1 * i c f a -> m Source #

(FoldableWithKey1 f, FoldableWithKey1 m) => FoldableWithKey1 (Compose * * f m) Source # 

Methods

foldMapWithKey1 :: Semigroup m => (Key (Compose * * f m) -> a -> m) -> Compose * * f m a -> m 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

traverseWithKey

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 [] Source # 

Methods

traverseWithKey :: Applicative f => (Key [] -> a -> f b) -> [a] -> f [b] Source #

mapWithKeyM :: Monad m => (Key [] -> a -> m b) -> [a] -> m [b] Source #

TraversableWithKey Maybe Source # 

Methods

traverseWithKey :: Applicative f => (Key Maybe -> a -> f b) -> Maybe a -> f (Maybe b) Source #

mapWithKeyM :: Monad m => (Key Maybe -> a -> m b) -> Maybe a -> m (Maybe b) Source #

TraversableWithKey Par1 Source # 

Methods

traverseWithKey :: Applicative f => (Key Par1 -> a -> f b) -> Par1 a -> f (Par1 b) Source #

mapWithKeyM :: Monad m => (Key Par1 -> a -> m b) -> Par1 a -> m (Par1 b) Source #

TraversableWithKey NonEmpty Source # 

Methods

traverseWithKey :: Applicative f => (Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b) Source #

mapWithKeyM :: Monad m => (Key NonEmpty -> a -> m b) -> NonEmpty a -> m (NonEmpty b) Source #

TraversableWithKey ZipList Source # 

Methods

traverseWithKey :: Applicative f => (Key ZipList -> a -> f b) -> ZipList a -> f (ZipList b) Source #

mapWithKeyM :: Monad m => (Key ZipList -> a -> m b) -> ZipList a -> m (ZipList b) Source #

TraversableWithKey Identity Source # 

Methods

traverseWithKey :: Applicative f => (Key Identity -> a -> f b) -> Identity a -> f (Identity b) Source #

mapWithKeyM :: Monad m => (Key Identity -> a -> m b) -> Identity a -> m (Identity b) Source #

TraversableWithKey IntMap Source # 

Methods

traverseWithKey :: Applicative f => (Key IntMap -> a -> f b) -> IntMap a -> f (IntMap b) Source #

mapWithKeyM :: Monad m => (Key IntMap -> a -> m b) -> IntMap a -> m (IntMap b) Source #

TraversableWithKey Tree Source # 

Methods

traverseWithKey :: Applicative f => (Key Tree -> a -> f b) -> Tree a -> f (Tree b) Source #

mapWithKeyM :: Monad m => (Key Tree -> a -> m b) -> Tree a -> m (Tree b) Source #

TraversableWithKey Seq Source # 

Methods

traverseWithKey :: Applicative f => (Key Seq -> a -> f b) -> Seq a -> f (Seq b) Source #

mapWithKeyM :: Monad m => (Key Seq -> a -> m b) -> Seq a -> m (Seq b) Source #

TraversableWithKey (V1 *) Source # 

Methods

traverseWithKey :: Applicative f => (Key (V1 *) -> a -> f b) -> V1 * a -> f (V1 * b) Source #

mapWithKeyM :: Monad m => (Key (V1 *) -> a -> m b) -> V1 * a -> m (V1 * b) Source #

TraversableWithKey (U1 *) Source # 

Methods

traverseWithKey :: Applicative f => (Key (U1 *) -> a -> f b) -> U1 * a -> f (U1 * b) Source #

mapWithKeyM :: Monad m => (Key (U1 *) -> a -> m b) -> U1 * a -> m (U1 * b) Source #

TraversableWithKey ((,) k) Source # 

Methods

traverseWithKey :: Applicative f => (Key ((,) k) -> a -> f b) -> (k, a) -> f (k, b) Source #

mapWithKeyM :: Monad m => (Key ((,) k) -> a -> m b) -> (k, a) -> m (k, b) Source #

Ix i => TraversableWithKey (Array i) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Array i) -> a -> f b) -> Array i a -> f (Array i b) Source #

mapWithKeyM :: Monad m => (Key (Array i) -> a -> m b) -> Array i a -> m (Array i b) Source #

TraversableWithKey (Proxy *) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Proxy *) -> a -> f b) -> Proxy * a -> f (Proxy * b) Source #

mapWithKeyM :: Monad m => (Key (Proxy *) -> a -> m b) -> Proxy * a -> m (Proxy * b) Source #

TraversableWithKey (Map k) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Map k) -> a -> f b) -> Map k a -> f (Map k b) Source #

mapWithKeyM :: Monad m => (Key (Map k) -> a -> m b) -> Map k a -> m (Map k b) Source #

TraversableWithKey f => TraversableWithKey (Cofree f) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b) Source #

mapWithKeyM :: Monad m => (Key (Cofree f) -> a -> m b) -> Cofree f a -> m (Cofree f b) Source #

TraversableWithKey f => TraversableWithKey (Free f) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Free f) -> a -> f b) -> Free f a -> f (Free f b) Source #

mapWithKeyM :: Monad m => (Key (Free f) -> a -> m b) -> Free f a -> m (Free f b) Source #

TraversableWithKey (HashMap k) Source # 

Methods

traverseWithKey :: Applicative f => (Key (HashMap k) -> a -> f b) -> HashMap k a -> f (HashMap k b) Source #

mapWithKeyM :: Monad m => (Key (HashMap k) -> a -> m b) -> HashMap k a -> m (HashMap k b) Source #

TraversableWithKey f => TraversableWithKey (Rec1 * f) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Rec1 * f) -> a -> f b) -> Rec1 * f a -> f (Rec1 * f b) Source #

mapWithKeyM :: Monad m => (Key (Rec1 * f) -> a -> m b) -> Rec1 * f a -> m (Rec1 * f b) Source #

TraversableWithKey m => TraversableWithKey (IdentityT * m) Source # 

Methods

traverseWithKey :: Applicative f => (Key (IdentityT * m) -> a -> f b) -> IdentityT * m a -> f (IdentityT * m b) Source #

mapWithKeyM :: Monad m => (Key (IdentityT * m) -> a -> m b) -> IdentityT * m a -> m (IdentityT * m b) Source #

TraversableWithKey (Tagged * a) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Tagged * a) -> a -> f b) -> Tagged * a a -> f (Tagged * a b) Source #

mapWithKeyM :: Monad m => (Key (Tagged * a) -> a -> m b) -> Tagged * a a -> m (Tagged * a b) Source #

TraversableWithKey (K1 * i c) Source # 

Methods

traverseWithKey :: Applicative f => (Key (K1 * i c) -> a -> f b) -> K1 * i c a -> f (K1 * i c b) Source #

mapWithKeyM :: Monad m => (Key (K1 * i c) -> a -> m b) -> K1 * i c a -> m (K1 * i c b) Source #

(TraversableWithKey f, TraversableWithKey g) => TraversableWithKey ((:+:) * f g) Source # 

Methods

traverseWithKey :: Applicative f => (Key ((* :+: f) g) -> a -> f b) -> (* :+: f) g a -> f ((* :+: f) g b) Source #

mapWithKeyM :: Monad m => (Key ((* :+: f) g) -> a -> m b) -> (* :+: f) g a -> m ((* :+: f) g b) Source #

(TraversableWithKey f, TraversableWithKey g) => TraversableWithKey ((:*:) * f g) Source # 

Methods

traverseWithKey :: Applicative f => (Key ((* :*: f) g) -> a -> f b) -> (* :*: f) g a -> f ((* :*: f) g b) Source #

mapWithKeyM :: Monad m => (Key ((* :*: f) g) -> a -> m b) -> (* :*: f) g a -> m ((* :*: f) g b) Source #

(TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (Product * f g) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Product * f g) -> a -> f b) -> Product * f g a -> f (Product * f g b) Source #

mapWithKeyM :: Monad m => (Key (Product * f g) -> a -> m b) -> Product * f g a -> m (Product * f g b) Source #

(TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (Sum * f g) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Sum * f g) -> a -> f b) -> Sum * f g a -> f (Sum * f g b) Source #

mapWithKeyM :: Monad m => (Key (Sum * f g) -> a -> m b) -> Sum * f g a -> m (Sum * f g b) Source #

TraversableWithKey f => TraversableWithKey (M1 * i c f) Source # 

Methods

traverseWithKey :: Applicative f => (Key (M1 * i c f) -> a -> f b) -> M1 * i c f a -> f (M1 * i c f b) Source #

mapWithKeyM :: Monad m => (Key (M1 * i c f) -> a -> m b) -> M1 * i c f a -> m (M1 * i c f b) Source #

(TraversableWithKey f, TraversableWithKey m) => TraversableWithKey (Compose * * f m) Source # 

Methods

traverseWithKey :: Applicative f => (Key (Compose * * f m) -> a -> f b) -> Compose * * f m a -> f (Compose * * f m b) Source #

mapWithKeyM :: Monad m => (Key (Compose * * f m) -> a -> m b) -> Compose * * f m a -> m (Compose * * f m b) Source #

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 #

Minimal complete definition

traverseWithKey1

Methods

traverseWithKey1 :: Apply f => (Key t -> a -> f b) -> t a -> f (t b) Source #

Instances

TraversableWithKey1 Par1 Source # 

Methods

traverseWithKey1 :: Apply f => (Key Par1 -> a -> f b) -> Par1 a -> f (Par1 b) Source #

TraversableWithKey1 NonEmpty Source # 

Methods

traverseWithKey1 :: Apply f => (Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b) Source #

TraversableWithKey1 Identity Source # 

Methods

traverseWithKey1 :: Apply f => (Key Identity -> a -> f b) -> Identity a -> f (Identity b) Source #

TraversableWithKey1 Tree Source # 

Methods

traverseWithKey1 :: Apply f => (Key Tree -> a -> f b) -> Tree a -> f (Tree b) Source #

TraversableWithKey1 (V1 *) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (V1 *) -> a -> f b) -> V1 * a -> f (V1 * b) Source #

TraversableWithKey1 ((,) k) Source # 

Methods

traverseWithKey1 :: Apply f => (Key ((,) k) -> a -> f b) -> (k, a) -> f (k, b) Source #

TraversableWithKey1 f => TraversableWithKey1 (Cofree f) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b) Source #

TraversableWithKey1 f => TraversableWithKey1 (Free f) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Free f) -> a -> f b) -> Free f a -> f (Free f b) Source #

TraversableWithKey1 f => TraversableWithKey1 (Rec1 * f) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Rec1 * f) -> a -> f b) -> Rec1 * f a -> f (Rec1 * f b) Source #

TraversableWithKey1 m => TraversableWithKey1 (IdentityT * m) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (IdentityT * m) -> a -> f b) -> IdentityT * m a -> f (IdentityT * m b) Source #

TraversableWithKey1 (Tagged * a) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Tagged * a) -> a -> f b) -> Tagged * a a -> f (Tagged * a b) Source #

(TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 ((:+:) * f g) Source # 

Methods

traverseWithKey1 :: Apply f => (Key ((* :+: f) g) -> a -> f b) -> (* :+: f) g a -> f ((* :+: f) g b) Source #

(TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 ((:*:) * f g) Source # 

Methods

traverseWithKey1 :: Apply f => (Key ((* :*: f) g) -> a -> f b) -> (* :*: f) g a -> f ((* :*: f) g b) Source #

(TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (Product * f g) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Product * f g) -> a -> f b) -> Product * f g a -> f (Product * f g b) Source #

(TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (Sum * f g) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Sum * f g) -> a -> f b) -> Sum * f g a -> f (Sum * f g b) Source #

TraversableWithKey1 f => TraversableWithKey1 (M1 * i c f) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (M1 * i c f) -> a -> f b) -> M1 * i c f a -> f (M1 * i c f b) Source #

(TraversableWithKey1 f, TraversableWithKey1 m) => TraversableWithKey1 (Compose * * f m) Source # 

Methods

traverseWithKey1 :: Apply f => (Key (Compose * * f m) -> a -> f b) -> Compose * * f m a -> f (Compose * * f m b) Source #

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