{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE CPP #-}
module Data.Key (
Key
, Keyed(..)
, (<#$>)
, keyed
, Zip(..)
, ZipWithKey(..)
, Indexable(..)
, (!)
, Lookup(..)
, lookupDefault
, Adjustable(..)
, FoldableWithKey(..)
, foldrWithKey'
, foldlWithKey'
, foldrWithKeyM
, foldlWithKeyM
, traverseWithKey_
, forWithKey_
, mapWithKeyM_
, forWithKeyM_
, concatMapWithKey
, anyWithKey
, allWithKey
, findWithKey
, FoldableWithKey1(..)
, traverseWithKey1_
, forWithKey1_
, foldMapWithKeyDefault1
, TraversableWithKey(..)
, forWithKey
, forWithKeyM
, mapAccumWithKeyL
, mapAccumWithKeyR
, mapWithKeyDefault
, foldMapWithKeyDefault
, TraversableWithKey1(..)
, foldMapWithKey1Default
) where
import Control.Applicative
import Control.Comonad.Trans.Traced
import Control.Monad.Free
import Control.Comonad.Cofree
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Reader
import qualified Data.Array as Array
import Data.Array (Array)
import Data.Functor.Identity
import Data.Functor.Bind
import Data.Functor.Compose
import Data.Functor.Constant
import Data.Functor.Product
import qualified Data.Functor.Sum as Functor
import Data.Foldable
import Data.Hashable
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.Ix hiding (index)
import Data.Map (Map)
import qualified Data.Map as Map
#ifdef MIN_VERSION_base_orphans
import Data.Orphans ()
#endif
import Data.Proxy
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe (fromJust, listToMaybe)
import qualified Data.Monoid as Monoid
import Data.Semigroup hiding (Product)
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import Data.Sequence (Seq, ViewL(EmptyL), viewl, (|>))
import qualified Data.Sequence as Seq
import Data.Tagged
import Data.Traversable
import Data.Tree
import qualified Data.List as List
import Data.Void
import GHC.Generics
import Prelude hiding (lookup, zip, zipWith)
type family Key (f :: * -> *)
type instance Key (Cofree f) = Seq (Key f)
type instance Key (Free f) = Seq (Key f)
type instance Key Tree = Seq Int
type instance Key NonEmpty = Int
type instance Key U1 = Void
type instance Key V1 = Void
type instance Key Par1 = ()
type instance Key Proxy = Void
type instance Key (Tagged a) = ()
type instance Key (Const e) = Void
type instance Key (Constant e) = Void
type instance Key (g :.: f) = (Key g, Key f)
type instance Key (f :*: g) = Either (Key f) (Key g)
type instance Key (f :+: g) = Either (Key f) (Key g)
type instance Key (Rec1 f) = Key f
type instance Key (M1 i c f) = Key f
type instance Key (K1 i c) = Void
class Functor f => Keyed f where
mapWithKey :: (Key f -> a -> b) -> f a -> f b
instance Keyed f => Keyed (Free f) where
mapWithKey :: forall a b. (Key (Free f) -> a -> b) -> Free f a -> Free f b
mapWithKey Key (Free f) -> a -> b
f (Pure a
a) = b -> Free f b
forall (f :: * -> *) a. a -> Free f a
Pure (Key (Free f) -> a -> b
f Seq (Key f)
Key (Free f)
forall a. Seq a
Seq.empty a
a)
mapWithKey Key (Free f) -> a -> b
f (Free f (Free f a)
as) = f (Free f b) -> Free f b
forall (f :: * -> *) a. f (Free f a) -> Free f a
Free ((Key f -> Free f a -> Free f b) -> f (Free f a) -> f (Free f b)
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Seq (Key f) -> a -> b) -> Free f a -> Free f b
(Key (Free f) -> a -> b) -> Free f a -> Free f b
forall a b. (Key (Free f) -> a -> b) -> Free f a -> Free f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Seq (Key f) -> a -> b) -> Free f a -> Free f b)
-> (Key f -> Seq (Key f) -> a -> b)
-> Key f
-> Free f a
-> Free f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> b)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> b
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> b
Key (Free f) -> a -> b
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> b)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Free f a)
as)
instance Keyed f => Keyed (Cofree f) where
mapWithKey :: forall a b. (Key (Cofree f) -> a -> b) -> Cofree f a -> Cofree f b
mapWithKey Key (Cofree f) -> a -> b
f (a
a :< f (Cofree f a)
as) = Key (Cofree f) -> a -> b
f Seq (Key f)
Key (Cofree f)
forall a. Seq a
Seq.empty a
a b -> f (Cofree f b) -> Cofree f b
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (Key f -> Cofree f a -> Cofree f b)
-> f (Cofree f a) -> f (Cofree f b)
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Seq (Key f) -> a -> b) -> Cofree f a -> Cofree f b
(Key (Cofree f) -> a -> b) -> Cofree f a -> Cofree f b
forall a b. (Key (Cofree f) -> a -> b) -> Cofree f a -> Cofree f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Seq (Key f) -> a -> b) -> Cofree f a -> Cofree f b)
-> (Key f -> Seq (Key f) -> a -> b)
-> Key f
-> Cofree f a
-> Cofree f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> b)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> b
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> b
Key (Cofree f) -> a -> b
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> b)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Cofree f a)
as
instance Keyed Tree where
mapWithKey :: forall a b. (Key Tree -> a -> b) -> Tree a -> Tree b
mapWithKey Key Tree -> a -> b
f (Node a
a [Tree a]
as) = b -> [Tree b] -> Tree b
forall a. a -> [Tree a] -> Tree a
Node (Key Tree -> a -> b
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a) ((Key [] -> Tree a -> Tree b) -> [Tree a] -> [Tree b]
forall a b. (Key [] -> a -> b) -> [a] -> [b]
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Seq Int -> a -> b) -> Tree a -> Tree b
(Key Tree -> a -> b) -> Tree a -> Tree b
forall a b. (Key Tree -> a -> b) -> Tree a -> Tree b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Seq Int -> a -> b) -> Tree a -> Tree b)
-> (Int -> Seq Int -> a -> b) -> Int -> Tree a -> Tree b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> a -> b) -> (Seq Int -> Seq Int) -> Seq Int -> a -> b
forall a b. (a -> b) -> (Seq Int -> a) -> Seq Int -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq Int -> a -> b
Key Tree -> a -> b
f ((Seq Int -> Seq Int) -> Seq Int -> a -> b)
-> (Int -> Seq Int -> Seq Int) -> Int -> Seq Int -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>)) [Tree a]
as)
instance Keyed U1 where
mapWithKey :: forall a b. (Key U1 -> a -> b) -> U1 a -> U1 b
mapWithKey Key U1 -> a -> b
_ U1 a
U1 = U1 b
forall k (p :: k). U1 p
U1
instance Keyed V1 where
mapWithKey :: forall a b. (Key V1 -> a -> b) -> V1 a -> V1 b
mapWithKey Key V1 -> a -> b
_ V1 a
v = V1 a
v V1 a -> V1 b -> V1 b
forall a b. a -> b -> b
`seq` V1 b
forall a. HasCallStack => a
undefined
instance Keyed Par1 where
mapWithKey :: forall a b. (Key Par1 -> a -> b) -> Par1 a -> Par1 b
mapWithKey Key Par1 -> a -> b
q = (a -> b) -> Par1 a -> Par1 b
forall a b. (a -> b) -> Par1 a -> Par1 b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key Par1 -> a -> b
q ())
instance Keyed (K1 i c) where
mapWithKey :: forall a b. (Key (K1 i c) -> a -> b) -> K1 i c a -> K1 i c b
mapWithKey Key (K1 i c) -> a -> b
_ (K1 c
c) = c -> K1 i c b
forall k i c (p :: k). c -> K1 i c p
K1 c
c
instance Keyed (Tagged a) where
mapWithKey :: forall a b. (Key (Tagged a) -> a -> b) -> Tagged a a -> Tagged a b
mapWithKey Key (Tagged a) -> a -> b
q (Tagged a
a) = b -> Tagged a b
forall {k} (s :: k) b. b -> Tagged s b
Tagged (Key (Tagged a) -> a -> b
q () a
a)
instance Keyed Proxy where
mapWithKey :: forall a b. (Key Proxy -> a -> b) -> Proxy a -> Proxy b
mapWithKey Key Proxy -> a -> b
_ Proxy a
Proxy = Proxy b
forall {k} (t :: k). Proxy t
Proxy
instance Keyed (Const e) where
mapWithKey :: forall a b. (Key (Const e) -> a -> b) -> Const e a -> Const e b
mapWithKey Key (Const e) -> a -> b
_ (Const e
a) = e -> Const e b
forall {k} a (b :: k). a -> Const a b
Const e
a
instance Keyed (Constant e) where
mapWithKey :: forall a b.
(Key (Constant e) -> a -> b) -> Constant e a -> Constant e b
mapWithKey Key (Constant e) -> a -> b
_ (Constant e
a) = e -> Constant e b
forall {k} a (b :: k). a -> Constant a b
Constant e
a
instance Keyed f => Keyed (M1 i c f) where
mapWithKey :: forall a b. (Key (M1 i c f) -> a -> b) -> M1 i c f a -> M1 i c f b
mapWithKey Key (M1 i c f) -> a -> b
q (M1 f a
f) = f b -> M1 i c f b
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 ((Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey Key f -> a -> b
Key (M1 i c f) -> a -> b
q f a
f)
instance Keyed f => Keyed (Rec1 f) where
mapWithKey :: forall a b. (Key (Rec1 f) -> a -> b) -> Rec1 f a -> Rec1 f b
mapWithKey Key (Rec1 f) -> a -> b
q (Rec1 f a
f) = f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 ((Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey Key f -> a -> b
Key (Rec1 f) -> a -> b
q f a
f)
instance (Keyed g, Keyed f) => Keyed (f :*: g) where
mapWithKey :: forall a b. (Key (f :*: g) -> a -> b) -> (:*:) f g a -> (:*:) f g b
mapWithKey Key (f :*: g) -> a -> b
q (f a
fa :*: g a
ga) = (Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (f :*: g) -> a -> b
q (Either (Key f) (Key g) -> a -> b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
fa f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (Key g -> a -> b) -> g a -> g b
forall a b. (Key g -> a -> b) -> g a -> g b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (f :*: g) -> a -> b
q (Either (Key f) (Key g) -> a -> b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
ga
instance (Keyed g, Keyed f) => Keyed (f :+: g) where
mapWithKey :: forall a b. (Key (f :+: g) -> a -> b) -> (:+:) f g a -> (:+:) f g b
mapWithKey Key (f :+: g) -> a -> b
q (L1 f a
fa) = f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 ((Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (f :+: g) -> a -> b
q (Either (Key f) (Key g) -> a -> b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
fa)
mapWithKey Key (f :+: g) -> a -> b
q (R1 g a
ga) = g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 ((Key g -> a -> b) -> g a -> g b
forall a b. (Key g -> a -> b) -> g a -> g b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (f :+: g) -> a -> b
q (Either (Key f) (Key g) -> a -> b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
ga)
instance (Keyed g, Keyed f) => Keyed (g :.: f) where
mapWithKey :: forall a b. (Key (g :.: f) -> a -> b) -> (:.:) g f a -> (:.:) g f b
mapWithKey Key (g :.: f) -> a -> b
q = (g (f a) -> g (f b)) -> (:.:) g f a -> (:.:) g f b
forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a'.
(g (f a) -> g' (f' a')) -> (:.:) g f a -> (:.:) g' f' a'
inComp ((Key g -> f a -> f b) -> g (f a) -> g (f b)
forall a b. (Key g -> a -> b) -> g a -> g b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Key f -> a -> b) -> f a -> f b)
-> (Key g -> Key f -> a -> b) -> Key g -> f a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key g, Key f) -> a -> b)
-> (Key f -> (Key g, Key f)) -> Key f -> a -> b
forall a b. (a -> b) -> (Key f -> a) -> Key f -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key g, Key f) -> a -> b
Key (g :.: f) -> a -> b
q ((Key f -> (Key g, Key f)) -> Key f -> a -> b)
-> (Key g -> Key f -> (Key g, Key f)) -> Key g -> Key f -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,)))
#if 0
mapWithKey :: (Key (g :.: f) -> a -> b) -> (g :.: f) a -> (g :.: f) b
:: ((Key g, Key f) -> a -> b) -> (g :.: f) a -> (g :.: f) b
mapWithKey q
= \ (Comp1 gfa) -> Comp1 (mapWithKey (\ gk -> mapWithKey (\ fk a -> q (gk, fk) a)) gfa)
= inComp $ mapWithKey (\ gk -> mapWithKey (\ fk a -> q (gk, fk) a))
= inComp $ mapWithKey (\ gk -> mapWithKey (\ fk -> q (gk, fk)))
= inComp $ mapWithKey (\ gk -> mapWithKey (q . (gk,)))
= inComp $ mapWithKey (\ gk -> mapWithKey . (q .) $ (gk,))
= inComp $ mapWithKey (\ gk -> mapWithKey . (q .) $ (,) gk)
= inComp (mapWithKey (mapWithKey . fmap q . (,)))
q :: ((Key g, Key f) -> a -> b)
gfa :: g (f a)
gk :: Key g
fk :: Key f
#endif
class Functor f => Zip f where
zipWith :: (a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f f a
a f b
b = (a -> b -> c) -> (a, b) -> c
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> b -> c
f ((a, b) -> c) -> f (a, b) -> f c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a -> f b -> f (a, b)
forall a b. f a -> f b -> f (a, b)
forall (f :: * -> *) a b. Zip f => f a -> f b -> f (a, b)
zip f a
a f b
b
zip :: f a -> f b -> f (a, b)
zip = (a -> b -> (a, b)) -> f a -> f b -> f (a, b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith (,)
zap :: f (a -> b) -> f a -> f b
zap = ((a -> b) -> a -> b) -> f (a -> b) -> f a -> f b
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith (a -> b) -> a -> b
forall a. a -> a
id
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL zipWith | zip #-}
#endif
instance Zip f => Zip (Cofree f) where
zipWith :: forall a b c.
(a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c
zipWith a -> b -> c
f (a
a :< f (Cofree f a)
as) (b
b :< f (Cofree f b)
bs) = a -> b -> c
f a
a b
b c -> f (Cofree f c) -> Cofree f c
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (Cofree f a -> Cofree f b -> Cofree f c)
-> f (Cofree f a) -> f (Cofree f b) -> f (Cofree f c)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith ((a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c
forall a b c.
(a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f) f (Cofree f a)
as f (Cofree f b)
bs
instance Zip Tree where
zipWith :: forall a b c. (a -> b -> c) -> Tree a -> Tree b -> Tree c
zipWith a -> b -> c
f (Node a
a [Tree a]
as) (Node b
b [Tree b]
bs) = c -> [Tree c] -> Tree c
forall a. a -> [Tree a] -> Tree a
Node (a -> b -> c
f a
a b
b) ((Tree a -> Tree b -> Tree c) -> [Tree a] -> [Tree b] -> [Tree c]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith ((a -> b -> c) -> Tree a -> Tree b -> Tree c
forall a b c. (a -> b -> c) -> Tree a -> Tree b -> Tree c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f) [Tree a]
as [Tree b]
bs)
instance Zip Proxy where
zipWith :: forall a b c. (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c
zipWith = (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c
forall a b c. (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
instance Zip (Tagged a) where
zipWith :: forall a b c.
(a -> b -> c) -> Tagged a a -> Tagged a b -> Tagged a c
zipWith = (a -> b -> c) -> Tagged a a -> Tagged a b -> Tagged a c
forall a b c.
(a -> b -> c) -> Tagged a a -> Tagged a b -> Tagged a c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
instance Zip U1 where
zipWith :: forall a b c. (a -> b -> c) -> U1 a -> U1 b -> U1 c
zipWith = (a -> b -> c) -> U1 a -> U1 b -> U1 c
forall a b c. (a -> b -> c) -> U1 a -> U1 b -> U1 c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
instance Zip V1 where
zipWith :: forall a b c. (a -> b -> c) -> V1 a -> V1 b -> V1 c
zipWith a -> b -> c
_ V1 a
v = V1 a
v V1 a -> (V1 b -> V1 c) -> V1 b -> V1 c
forall a b. a -> b -> b
`seq` V1 b -> V1 c
forall a. HasCallStack => a
undefined
instance Zip Par1 where
zipWith :: forall a b c. (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c
zipWith = (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c
forall a b c. (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
instance (Zip f, Zip g) => Zip (f :*: g) where
zipWith :: forall a b c.
(a -> b -> c) -> (:*:) f g a -> (:*:) f g b -> (:*:) f g c
zipWith a -> b -> c
h (f a
fa :*: g a
ga) (f b
fa' :*: g b
ga') =
(a -> b -> c) -> f a -> f b -> f c
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
h f a
fa f b
fa' f c -> g c -> (:*:) f g c
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (a -> b -> c) -> g a -> g b -> g c
forall a b c. (a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
h g a
ga g b
ga'
instance (Zip f, Zip g) => Zip (g :.: f) where
zipWith :: forall a b c.
(a -> b -> c) -> (:.:) g f a -> (:.:) g f b -> (:.:) g f c
zipWith = (g (f a) -> g (f b) -> g (f c))
-> (:.:) g f a -> (:.:) g f b -> (:.:) g f c
forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a' (g'' :: * -> *) (f'' :: * -> *) a''.
(g (f a) -> g' (f' a') -> g'' (f'' a''))
-> (:.:) g f a -> (:.:) g' f' a' -> (:.:) g'' f'' a''
inComp2 ((g (f a) -> g (f b) -> g (f c))
-> (:.:) g f a -> (:.:) g f b -> (:.:) g f c)
-> ((a -> b -> c) -> g (f a) -> g (f b) -> g (f c))
-> (a -> b -> c)
-> (:.:) g f a
-> (:.:) g f b
-> (:.:) g f c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (f a -> f b -> f c) -> g (f a) -> g (f b) -> g (f c)
forall a b c. (a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith ((f a -> f b -> f c) -> g (f a) -> g (f b) -> g (f c))
-> ((a -> b -> c) -> f a -> f b -> f c)
-> (a -> b -> c)
-> g (f a)
-> g (f b)
-> g (f c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b -> c) -> f a -> f b -> f c
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith
instance Zip f => Zip (Rec1 f) where
zipWith :: forall a b c. (a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c
zipWith a -> b -> c
f (Rec1 f a
a) (Rec1 f b
b) = f c -> Rec1 f c
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 ((a -> b -> c) -> f a -> f b -> f c
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f f a
a f b
b)
instance Zip f => Zip (M1 i c f) where
zipWith :: forall a b c.
(a -> b -> c) -> M1 i c f a -> M1 i c f b -> M1 i c f c
zipWith a -> b -> c
f (M1 f a
a) (M1 f b
b) = f c -> M1 i c f c
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 ((a -> b -> c) -> f a -> f b -> f c
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f f a
a f b
b)
(<--) :: (b -> b') -> (a' -> a) -> ((a -> b) -> (a' -> b'))
(b -> b'
h <-- :: forall b b' a' a. (b -> b') -> (a' -> a) -> (a -> b) -> a' -> b'
<-- a' -> a
f) a -> b
g = b -> b'
h (b -> b') -> (a' -> b) -> a' -> b'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
g (a -> b) -> (a' -> a) -> a' -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a' -> a
f
inComp :: (g (f a) -> g' (f' a')) -> ((g :.: f) a -> (g' :.: f') a')
inComp :: forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a'.
(g (f a) -> g' (f' a')) -> (:.:) g f a -> (:.:) g' f' a'
inComp = g' (f' a') -> (:.:) g' f' a'
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 (g' (f' a') -> (:.:) g' f' a')
-> ((:.:) g f a -> g (f a))
-> (g (f a) -> g' (f' a'))
-> (:.:) g f a
-> (:.:) g' f' a'
forall b b' a' a. (b -> b') -> (a' -> a) -> (a -> b) -> a' -> b'
<-- (:.:) g f a -> g (f a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
unComp1
inComp2 :: ( g (f a) -> g' (f' a') -> g'' (f'' a''))
-> ((g :.: f) a -> (g' :.: f') a' -> (g'' :.: f'') a'')
inComp2 :: forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a' (g'' :: * -> *) (f'' :: * -> *) a''.
(g (f a) -> g' (f' a') -> g'' (f'' a''))
-> (:.:) g f a -> (:.:) g' f' a' -> (:.:) g'' f'' a''
inComp2 = (g' (f' a') -> g'' (f'' a''))
-> (:.:) g' f' a' -> (:.:) g'' f'' a''
forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a'.
(g (f a) -> g' (f' a')) -> (:.:) g f a -> (:.:) g' f' a'
inComp ((g' (f' a') -> g'' (f'' a''))
-> (:.:) g' f' a' -> (:.:) g'' f'' a'')
-> ((:.:) g f a -> g (f a))
-> (g (f a) -> g' (f' a') -> g'' (f'' a''))
-> (:.:) g f a
-> (:.:) g' f' a'
-> (:.:) g'' f'' a''
forall b b' a' a. (b -> b') -> (a' -> a) -> (a -> b) -> a' -> b'
<-- (:.:) g f a -> g (f a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
unComp1
class (Keyed f, Zip f) => ZipWithKey f where
zipWithKey :: (Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey Key f -> a -> b -> c
f = f (b -> c) -> f b -> f c
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Zip f => f (a -> b) -> f a -> f b
zap (f (b -> c) -> f b -> f c)
-> (f a -> f (b -> c)) -> f a -> f b -> f c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key f -> a -> b -> c) -> f a -> f (b -> c)
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey Key f -> a -> b -> c
f
zapWithKey :: f (Key f -> a -> b) -> f a -> f b
zapWithKey = (Key f -> (Key f -> a -> b) -> a -> b)
-> f (Key f -> a -> b) -> f a -> f b
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (\Key f
k Key f -> a -> b
f -> Key f -> a -> b
f Key f
k)
instance ZipWithKey f => ZipWithKey (Cofree f) where
zipWithKey :: forall a b c.
(Key (Cofree f) -> a -> b -> c)
-> Cofree f a -> Cofree f b -> Cofree f c
zipWithKey Key (Cofree f) -> a -> b -> c
f (a
a :< f (Cofree f a)
as) (b
b :< f (Cofree f b)
bs) = Key (Cofree f) -> a -> b -> c
f Seq (Key f)
Key (Cofree f)
forall a. Seq a
Seq.empty a
a b
b c -> f (Cofree f c) -> Cofree f c
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (Key f -> Cofree f a -> Cofree f b -> Cofree f c)
-> f (Cofree f a) -> f (Cofree f b) -> f (Cofree f c)
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((Seq (Key f) -> a -> b -> c)
-> Cofree f a -> Cofree f b -> Cofree f c
(Key (Cofree f) -> a -> b -> c)
-> Cofree f a -> Cofree f b -> Cofree f c
forall a b c.
(Key (Cofree f) -> a -> b -> c)
-> Cofree f a -> Cofree f b -> Cofree f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((Seq (Key f) -> a -> b -> c)
-> Cofree f a -> Cofree f b -> Cofree f c)
-> (Key f -> Seq (Key f) -> a -> b -> c)
-> Key f
-> Cofree f a
-> Cofree f b
-> Cofree f c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> b -> c)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> b -> c
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> b -> c
Key (Cofree f) -> a -> b -> c
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> b -> c)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> b
-> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Cofree f a)
as f (Cofree f b)
bs
instance ZipWithKey Tree where
zipWithKey :: forall a b c.
(Key Tree -> a -> b -> c) -> Tree a -> Tree b -> Tree c
zipWithKey Key Tree -> a -> b -> c
f (Node a
a [Tree a]
as) (Node b
b [Tree b]
bs) = Key Tree -> a -> b -> c
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a b
b c -> [Tree c] -> Tree c
forall a. a -> [Tree a] -> Tree a
`Node` (Key [] -> Tree a -> Tree b -> Tree c)
-> [Tree a] -> [Tree b] -> [Tree c]
forall a b c. (Key [] -> a -> b -> c) -> [a] -> [b] -> [c]
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((Seq Int -> a -> b -> c) -> Tree a -> Tree b -> Tree c
(Key Tree -> a -> b -> c) -> Tree a -> Tree b -> Tree c
forall a b c.
(Key Tree -> a -> b -> c) -> Tree a -> Tree b -> Tree c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((Seq Int -> a -> b -> c) -> Tree a -> Tree b -> Tree c)
-> (Int -> Seq Int -> a -> b -> c)
-> Int
-> Tree a
-> Tree b
-> Tree c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> a -> b -> c)
-> (Seq Int -> Seq Int) -> Seq Int -> a -> b -> c
forall a b. (a -> b) -> (Seq Int -> a) -> Seq Int -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq Int -> a -> b -> c
Key Tree -> a -> b -> c
f ((Seq Int -> Seq Int) -> Seq Int -> a -> b -> c)
-> (Int -> Seq Int -> Seq Int) -> Int -> Seq Int -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>)) [Tree a]
as [Tree b]
bs
instance ZipWithKey (Tagged a) where
zipWithKey :: forall a b c.
(Key (Tagged a) -> a -> b -> c)
-> Tagged a a -> Tagged a b -> Tagged a c
zipWithKey Key (Tagged a) -> a -> b -> c
f = (a -> b -> c) -> Tagged a a -> Tagged a b -> Tagged a c
forall a b c.
(a -> b -> c) -> Tagged a a -> Tagged a b -> Tagged a c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith (Key (Tagged a) -> a -> b -> c
f ())
instance ZipWithKey Proxy where
zipWithKey :: forall a b c.
(Key Proxy -> a -> b -> c) -> Proxy a -> Proxy b -> Proxy c
zipWithKey Key Proxy -> a -> b -> c
_ Proxy a
_ Proxy b
_ = Proxy c
forall {k} (t :: k). Proxy t
Proxy
instance ZipWithKey U1 where
zipWithKey :: forall a b c. (Key U1 -> a -> b -> c) -> U1 a -> U1 b -> U1 c
zipWithKey Key U1 -> a -> b -> c
_ U1 a
_ U1 b
_ = U1 c
forall k (p :: k). U1 p
U1
instance ZipWithKey V1 where
zipWithKey :: forall a b c. (Key V1 -> a -> b -> c) -> V1 a -> V1 b -> V1 c
zipWithKey Key V1 -> a -> b -> c
_ V1 a
u V1 b
v = V1 a
u V1 a -> V1 c -> V1 c
forall a b. a -> b -> b
`seq` V1 b
v V1 b -> V1 c -> V1 c
forall a b. a -> b -> b
`seq` V1 c
forall a. HasCallStack => a
undefined
instance ZipWithKey Par1 where
zipWithKey :: forall a b c.
(Key Par1 -> a -> b -> c) -> Par1 a -> Par1 b -> Par1 c
zipWithKey Key Par1 -> a -> b -> c
f (Par1 a
a) (Par1 b
b) = c -> Par1 c
forall p. p -> Par1 p
Par1 (Key Par1 -> a -> b -> c
f () a
a b
b)
instance ZipWithKey f => ZipWithKey (Rec1 f) where
zipWithKey :: forall a b c.
(Key (Rec1 f) -> a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c
zipWithKey Key (Rec1 f) -> a -> b -> c
f (Rec1 f a
a) (Rec1 f b
b) = f c -> Rec1 f c
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 ((Key f -> a -> b -> c) -> f a -> f b -> f c
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey Key f -> a -> b -> c
Key (Rec1 f) -> a -> b -> c
f f a
a f b
b)
instance ZipWithKey f => ZipWithKey (M1 i c f) where
zipWithKey :: forall a b c.
(Key (M1 i c f) -> a -> b -> c)
-> M1 i c f a -> M1 i c f b -> M1 i c f c
zipWithKey Key (M1 i c f) -> a -> b -> c
f (M1 f a
a) (M1 f b
b) = f c -> M1 i c f c
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 ((Key f -> a -> b -> c) -> f a -> f b -> f c
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey Key f -> a -> b -> c
Key (M1 i c f) -> a -> b -> c
f f a
a f b
b)
instance (ZipWithKey f, ZipWithKey g) => ZipWithKey (f :*: g) where
zipWithKey :: forall a b c.
(Key (f :*: g) -> a -> b -> c)
-> (:*:) f g a -> (:*:) f g b -> (:*:) f g c
zipWithKey Key (f :*: g) -> a -> b -> c
f (f a
as :*: g a
bs) (f b
cs :*: g b
ds) = (Key f -> a -> b -> c) -> f a -> f b -> f c
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (Either (Key f) (Key g) -> a -> b -> c
Key (f :*: g) -> a -> b -> c
f (Either (Key f) (Key g) -> a -> b -> c)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
as f b
cs f c -> g c -> (:*:) f g c
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (Key g -> a -> b -> c) -> g a -> g b -> g c
forall a b c. (Key g -> a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (Either (Key f) (Key g) -> a -> b -> c
Key (f :*: g) -> a -> b -> c
f (Either (Key f) (Key g) -> a -> b -> c)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
bs g b
ds
instance (ZipWithKey f, ZipWithKey g) => ZipWithKey (g :.: f) where
zipWithKey :: forall a b c.
(Key (g :.: f) -> a -> b -> c)
-> (:.:) g f a -> (:.:) g f b -> (:.:) g f c
zipWithKey Key (g :.: f) -> a -> b -> c
f (Comp1 g (f a)
xs) (Comp1 g (f b)
ys) = g (f c) -> (:.:) g f c
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 (g (f c) -> (:.:) g f c) -> g (f c) -> (:.:) g f c
forall a b. (a -> b) -> a -> b
$ (Key g -> f a -> f b -> f c) -> g (f a) -> g (f b) -> g (f c)
forall a b c. (Key g -> a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (\Key g
a -> (Key f -> a -> b -> c) -> f a -> f b -> f c
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (\Key f
b -> Key (g :.: f) -> a -> b -> c
f (Key g
a,Key f
b))) g (f a)
xs g (f b)
ys
infixl 4 <#$>
(<#$>) :: Keyed f => (Key f -> a -> b) -> f a -> f b
<#$> :: forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
(<#$>) = (Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey
{-# INLINE (<#$>) #-}
keyed :: Keyed f => f a -> f (Key f, a)
keyed :: forall (f :: * -> *) a. Keyed f => f a -> f (Key f, a)
keyed = (Key f -> a -> (Key f, a)) -> f a -> f (Key f, a)
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (,)
{-# INLINE keyed #-}
class Lookup f => Indexable f where
index :: f a -> Key f -> a
instance Indexable f => Indexable (Cofree f) where
index :: forall a. Cofree f a -> Key (Cofree f) -> a
index (a
a :< f (Cofree f a)
as) Key (Cofree f)
key = case Seq (Key f) -> ViewL (Key f)
forall a. Seq a -> ViewL a
viewl Seq (Key f)
Key (Cofree f)
key of
ViewL (Key f)
EmptyL -> a
a
Key f
k Seq.:< Seq (Key f)
ks -> Cofree f a -> Key (Cofree f) -> a
forall a. Cofree f a -> Key (Cofree f) -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index (f (Cofree f a) -> Key f -> Cofree f a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f (Cofree f a)
as Key f
k) Seq (Key f)
Key (Cofree f)
ks
instance Indexable (Tagged a) where
index :: forall a. Tagged a a -> Key (Tagged a) -> a
index (Tagged a
a) () = a
a
instance Indexable Proxy where
index :: forall a. Proxy a -> Key Proxy -> a
index Proxy a
Proxy = Void -> a
Key Proxy -> a
forall a. Void -> a
absurd
instance Indexable (Const e) where
index :: forall a. Const e a -> Key (Const e) -> a
index Const e a
_ = Void -> a
Key (Const e) -> a
forall a. Void -> a
absurd
instance Indexable (Constant e) where
index :: forall a. Constant e a -> Key (Constant e) -> a
index Constant e a
_ = Void -> a
Key (Constant e) -> a
forall a. Void -> a
absurd
instance Indexable Tree where
index :: forall a. Tree a -> Key Tree -> a
index (Node a
a [Tree a]
as) Key Tree
key = case Seq Int -> ViewL Int
forall a. Seq a -> ViewL a
viewl Seq Int
Key Tree
key of
ViewL Int
EmptyL -> a
a
Int
k Seq.:< Seq Int
ks -> Tree a -> Key Tree -> a
forall a. Tree a -> Key Tree -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index ([Tree a] -> Key [] -> Tree a
forall a. [a] -> Key [] -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index [Tree a]
as Int
Key []
k) Seq Int
Key Tree
ks
instance Indexable U1 where
index :: forall a. U1 a -> Key U1 -> a
index U1 a
U1 = Void -> a
Key U1 -> a
forall a. Void -> a
absurd
instance Indexable Par1 where
index :: forall a. Par1 a -> Key Par1 -> a
index (Par1 a
a) () = a
a
instance Indexable f => Indexable (Rec1 f) where
index :: forall a. Rec1 f a -> Key (Rec1 f) -> a
index (Rec1 f a
f) Key (Rec1 f)
a = f a -> Key f -> a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f a
f Key f
Key (Rec1 f)
a
instance Indexable f => Indexable (M1 i c f) where
index :: forall a. M1 i c f a -> Key (M1 i c f) -> a
index (M1 f a
f) Key (M1 i c f)
a = f a -> Key f -> a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f a
f Key f
Key (M1 i c f)
a
instance Indexable (K1 i c) where
index :: forall a. K1 i c a -> Key (K1 i c) -> a
index K1 i c a
_ = Void -> a
Key (K1 i c) -> a
forall a. Void -> a
absurd
instance (Indexable g, Indexable f) =>
Indexable (f :*: g) where
index :: forall a. (:*:) f g a -> Key (f :*: g) -> a
index (f a
fa :*: g a
_) (Left Key f
fk) = f a
fa f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
! Key f
fk
index (f a
_ :*: g a
ga) (Right Key g
gk) = g a
ga g a -> Key g -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
! Key g
gk
instance (Indexable g, Indexable f) =>
Indexable (g :.: f) where
index :: forall a. (:.:) g f a -> Key (g :.: f) -> a
index (Comp1 g (f a)
gfa) (Key g
gk,Key f
fk) = g (f a)
gfa g (f a) -> Key g -> f a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
! Key g
gk f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
! Key f
fk
(!) :: Indexable f => f a -> Key f -> a
! :: forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
(!) = f a -> Key f -> a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index
class Lookup f where
lookup :: Key f -> f a -> Maybe a
instance Lookup f => Lookup (Cofree f) where
lookup :: forall a. Key (Cofree f) -> Cofree f a -> Maybe a
lookup Key (Cofree f)
key (a
a :< f (Cofree f a)
as) = case Seq (Key f) -> ViewL (Key f)
forall a. Seq a -> ViewL a
viewl Seq (Key f)
Key (Cofree f)
key of
ViewL (Key f)
EmptyL -> a -> Maybe a
forall a. a -> Maybe a
Just a
a
Key f
k Seq.:< Seq (Key f)
ks -> Key f -> f (Cofree f a) -> Maybe (Cofree f a)
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
k f (Cofree f a)
as Maybe (Cofree f a) -> (Cofree f a -> Maybe a) -> Maybe a
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Key (Cofree f) -> Cofree f a -> Maybe a
forall a. Key (Cofree f) -> Cofree f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Seq (Key f)
Key (Cofree f)
ks
instance Lookup (Tagged a) where
lookup :: forall a. Key (Tagged a) -> Tagged a a -> Maybe a
lookup () (Tagged a
a) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
instance Lookup Proxy where
lookup :: forall a. Key Proxy -> Proxy a -> Maybe a
lookup Key Proxy
_ Proxy a
_ = Maybe a
forall a. Maybe a
Nothing
instance Lookup (Const e) where
lookup :: forall a. Key (Const e) -> Const e a -> Maybe a
lookup Key (Const e)
_ Const e a
_ = Maybe a
forall a. Maybe a
Nothing
instance Lookup (Constant e) where
lookup :: forall a. Key (Constant e) -> Constant e a -> Maybe a
lookup Key (Constant e)
_ Constant e a
_ = Maybe a
forall a. Maybe a
Nothing
instance Lookup Tree where
lookup :: forall a. Key Tree -> Tree a -> Maybe a
lookup Key Tree
key (Node a
a [Tree a]
as) = case Seq Int -> ViewL Int
forall a. Seq a -> ViewL a
viewl Seq Int
Key Tree
key of
ViewL Int
EmptyL -> a -> Maybe a
forall a. a -> Maybe a
Just a
a
Int
k Seq.:< Seq Int
ks -> Key [] -> [Tree a] -> Maybe (Tree a)
forall a. Key [] -> [a] -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Int
Key []
k [Tree a]
as Maybe (Tree a) -> (Tree a -> Maybe a) -> Maybe a
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Key Tree -> Tree a -> Maybe a
forall a. Key Tree -> Tree a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Seq Int
Key Tree
ks
instance Lookup f => Lookup (Free f) where
lookup :: forall a. Key (Free f) -> Free f a -> Maybe a
lookup Key (Free f)
key (Pure a
a)
| Seq (Key f) -> Bool
forall a. Seq a -> Bool
Seq.null Seq (Key f)
Key (Free f)
key = a -> Maybe a
forall a. a -> Maybe a
Just a
a
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
lookup Key (Free f)
key (Free f (Free f a)
as) = case Seq (Key f) -> ViewL (Key f)
forall a. Seq a -> ViewL a
viewl Seq (Key f)
Key (Free f)
key of
Key f
k Seq.:< Seq (Key f)
ks -> Key f -> f (Free f a) -> Maybe (Free f a)
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
k f (Free f a)
as Maybe (Free f a) -> (Free f a -> Maybe a) -> Maybe a
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Key (Free f) -> Free f a -> Maybe a
forall a. Key (Free f) -> Free f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Seq (Key f)
Key (Free f)
ks
ViewL (Key f)
_ -> Maybe a
forall a. Maybe a
Nothing
instance Lookup U1 where
lookup :: forall a. Key U1 -> U1 a -> Maybe a
lookup Key U1
_ U1 a
_ = Maybe a
forall a. Maybe a
Nothing
instance Lookup Par1 where
lookup :: forall a. Key Par1 -> Par1 a -> Maybe a
lookup = Key Par1 -> Par1 a -> Maybe a
forall (f :: * -> *) a. Indexable f => Key f -> f a -> Maybe a
lookupDefault
instance Lookup f => Lookup (Rec1 f) where
lookup :: forall a. Key (Rec1 f) -> Rec1 f a -> Maybe a
lookup Key (Rec1 f)
k (Rec1 f a
f) = Key f -> f a -> Maybe a
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
Key (Rec1 f)
k f a
f
instance Lookup f => Lookup (M1 i c f) where
lookup :: forall a. Key (M1 i c f) -> M1 i c f a -> Maybe a
lookup Key (M1 i c f)
k (M1 f a
f) = Key f -> f a -> Maybe a
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
Key (M1 i c f)
k f a
f
instance Lookup (K1 i c) where
lookup :: forall a. Key (K1 i c) -> K1 i c a -> Maybe a
lookup Key (K1 i c)
_ K1 i c a
_ = Maybe a
forall a. Maybe a
Nothing
instance (Indexable g, Indexable f) => Lookup (f :*: g) where
lookup :: forall a. Key (f :*: g) -> (:*:) f g a -> Maybe a
lookup = Key (f :*: g) -> (:*:) f g a -> Maybe a
forall (f :: * -> *) a. Indexable f => Key f -> f a -> Maybe a
lookupDefault
instance (Indexable g, Indexable f) => Lookup (g :.: f) where
lookup :: forall a. Key (g :.: f) -> (:.:) g f a -> Maybe a
lookup = Key (g :.: f) -> (:.:) g f a -> Maybe a
forall (f :: * -> *) a. Indexable f => Key f -> f a -> Maybe a
lookupDefault
lookupDefault :: Indexable f => Key f -> f a -> Maybe a
lookupDefault :: forall (f :: * -> *) a. Indexable f => Key f -> f a -> Maybe a
lookupDefault Key f
k f a
t = a -> Maybe a
forall a. a -> Maybe a
Just (f a -> Key f -> a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f a
t Key f
k)
class Functor f => Adjustable f where
adjust :: (a -> a) -> Key f -> f a -> f a
replace :: Key f -> a -> f a -> f a
replace Key f
k a
v = (a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust (a -> a -> a
forall a b. a -> b -> a
const a
v) Key f
k
instance Adjustable f => Adjustable (Free f) where
adjust :: forall a. (a -> a) -> Key (Free f) -> Free f a -> Free f a
adjust a -> a
f Key (Free f)
key as :: Free f a
as@(Pure a
a)
| Seq (Key f) -> Bool
forall a. Seq a -> Bool
Seq.null Seq (Key f)
Key (Free f)
key = a -> Free f a
forall (f :: * -> *) a. a -> Free f a
Pure (a -> Free f a) -> a -> Free f a
forall a b. (a -> b) -> a -> b
$ a -> a
f a
a
| Bool
otherwise = Free f a
as
adjust a -> a
f Key (Free f)
key aas :: Free f a
aas@(Free f (Free f a)
as) = case Seq (Key f) -> ViewL (Key f)
forall a. Seq a -> ViewL a
viewl Seq (Key f)
Key (Free f)
key of
Key f
k Seq.:< Seq (Key f)
ks -> f (Free f a) -> Free f a
forall (f :: * -> *) a. f (Free f a) -> Free f a
Free (f (Free f a) -> Free f a) -> f (Free f a) -> Free f a
forall a b. (a -> b) -> a -> b
$ (Free f a -> Free f a) -> Key f -> f (Free f a) -> f (Free f a)
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust ((a -> a) -> Key (Free f) -> Free f a -> Free f a
forall a. (a -> a) -> Key (Free f) -> Free f a -> Free f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Seq (Key f)
Key (Free f)
ks) Key f
k f (Free f a)
as
ViewL (Key f)
_ -> Free f a
aas
instance Adjustable f => Adjustable (Cofree f) where
adjust :: forall a. (a -> a) -> Key (Cofree f) -> Cofree f a -> Cofree f a
adjust a -> a
f Key (Cofree f)
key (a
a :< f (Cofree f a)
as) = case Seq (Key f) -> ViewL (Key f)
forall a. Seq a -> ViewL a
viewl Seq (Key f)
Key (Cofree f)
key of
Key f
k Seq.:< Seq (Key f)
ks -> a
a a -> f (Cofree f a) -> Cofree f a
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (Cofree f a -> Cofree f a)
-> Key f -> f (Cofree f a) -> f (Cofree f a)
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust ((a -> a) -> Key (Cofree f) -> Cofree f a -> Cofree f a
forall a. (a -> a) -> Key (Cofree f) -> Cofree f a -> Cofree f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Seq (Key f)
Key (Cofree f)
ks) Key f
k f (Cofree f a)
as
ViewL (Key f)
_ -> a -> a
f a
a a -> f (Cofree f a) -> Cofree f a
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< f (Cofree f a)
as
instance Adjustable Tree where
adjust :: forall a. (a -> a) -> Key Tree -> Tree a -> Tree a
adjust a -> a
f Key Tree
key (Node a
a [Tree a]
as) = case Seq Int -> ViewL Int
forall a. Seq a -> ViewL a
viewl Seq Int
Key Tree
key of
Int
k Seq.:< Seq Int
ks -> a
a a -> [Tree a] -> Tree a
forall a. a -> [Tree a] -> Tree a
`Node` (Tree a -> Tree a) -> Key [] -> [Tree a] -> [Tree a]
forall a. (a -> a) -> Key [] -> [a] -> [a]
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust ((a -> a) -> Key Tree -> Tree a -> Tree a
forall a. (a -> a) -> Key Tree -> Tree a -> Tree a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Seq Int
Key Tree
ks) Int
Key []
k [Tree a]
as
ViewL Int
_ -> a -> a
f a
a a -> [Tree a] -> Tree a
forall a. a -> [Tree a] -> Tree a
`Node` [Tree a]
as
instance Adjustable (Tagged a) where
adjust :: forall a. (a -> a) -> Key (Tagged a) -> Tagged a a -> Tagged a a
adjust a -> a
f Key (Tagged a)
_ (Tagged a
a) = a -> Tagged a a
forall {k} (s :: k) b. b -> Tagged s b
Tagged (a -> a
f a
a)
replace :: forall a. Key (Tagged a) -> a -> Tagged a a -> Tagged a a
replace Key (Tagged a)
_ a
a Tagged a a
_ = a -> Tagged a a
forall {k} (s :: k) b. b -> Tagged s b
Tagged a
a
instance Adjustable Proxy where
adjust :: forall a. (a -> a) -> Key Proxy -> Proxy a -> Proxy a
adjust a -> a
_ Key Proxy
_ Proxy a
_ = Proxy a
forall {k} (t :: k). Proxy t
Proxy
replace :: forall a. Key Proxy -> a -> Proxy a -> Proxy a
replace Key Proxy
_ a
_ Proxy a
_ = Proxy a
forall {k} (t :: k). Proxy t
Proxy
instance Adjustable (Const e) where
adjust :: forall a. (a -> a) -> Key (Const e) -> Const e a -> Const e a
adjust a -> a
_ Key (Const e)
_ Const e a
x = Const e a
x
replace :: forall a. Key (Const e) -> a -> Const e a -> Const e a
replace Key (Const e)
_ a
_ Const e a
x = Const e a
x
instance Adjustable (Constant e) where
adjust :: forall a.
(a -> a) -> Key (Constant e) -> Constant e a -> Constant e a
adjust a -> a
_ Key (Constant e)
_ Constant e a
x = Constant e a
x
replace :: forall a. Key (Constant e) -> a -> Constant e a -> Constant e a
replace Key (Constant e)
_ a
_ Constant e a
x = Constant e a
x
instance Adjustable U1 where
adjust :: forall a. (a -> a) -> Key U1 -> U1 a -> U1 a
adjust a -> a
_ Key U1
_ U1 a
_ = U1 a
forall k (p :: k). U1 p
U1
replace :: forall a. Key U1 -> a -> U1 a -> U1 a
replace Key U1
_ a
_ U1 a
_ = U1 a
forall k (p :: k). U1 p
U1
instance Adjustable Par1 where
adjust :: forall a. (a -> a) -> Key Par1 -> Par1 a -> Par1 a
adjust a -> a
h () = (a -> a) -> Par1 a -> Par1 a
forall a b. (a -> b) -> Par1 a -> Par1 b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
h
replace :: forall a. Key Par1 -> a -> Par1 a -> Par1 a
replace Key Par1
_ a
a Par1 a
_ = a -> Par1 a
forall p. p -> Par1 p
Par1 a
a
instance Adjustable f => Adjustable (Rec1 f) where
adjust :: forall a. (a -> a) -> Key (Rec1 f) -> Rec1 f a -> Rec1 f a
adjust a -> a
f Key (Rec1 f)
k (Rec1 f a
a) = f a -> Rec1 f a
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 ((a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key f
Key (Rec1 f)
k f a
a)
replace :: forall a. Key (Rec1 f) -> a -> Rec1 f a -> Rec1 f a
replace Key (Rec1 f)
k a
a (Rec1 f a
b) = f a -> Rec1 f a
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 (Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
Key (Rec1 f)
k a
a f a
b)
instance Adjustable f => Adjustable (M1 i c f) where
adjust :: forall a. (a -> a) -> Key (M1 i c f) -> M1 i c f a -> M1 i c f a
adjust a -> a
f Key (M1 i c f)
k (M1 f a
a) = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 ((a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key f
Key (M1 i c f)
k f a
a)
replace :: forall a. Key (M1 i c f) -> a -> M1 i c f a -> M1 i c f a
replace Key (M1 i c f)
k a
a (M1 f a
b) = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
Key (M1 i c f)
k a
a f a
b)
instance Adjustable (K1 i c) where
adjust :: forall a. (a -> a) -> Key (K1 i c) -> K1 i c a -> K1 i c a
adjust a -> a
_ Key (K1 i c)
_ K1 i c a
x = K1 i c a
x
replace :: forall a. Key (K1 i c) -> a -> K1 i c a -> K1 i c a
replace Key (K1 i c)
_ a
_ K1 i c a
x = K1 i c a
x
instance (Adjustable f, Adjustable g) => Adjustable (f :+: g) where
adjust :: forall a. (a -> a) -> Key (f :+: g) -> (:+:) f g a -> (:+:) f g a
adjust a -> a
h (Left Key f
a) (L1 f a
fa) = f a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 ((a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
h Key f
a f a
fa)
adjust a -> a
h (Right Key g
b) (R1 g a
fb) = g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 ((a -> a) -> Key g -> g a -> g a
forall a. (a -> a) -> Key g -> g a -> g a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
h Key g
b g a
fb)
adjust a -> a
_ Key (f :+: g)
_ (:+:) f g a
x = (:+:) f g a
x
replace :: forall a. Key (f :+: g) -> a -> (:+:) f g a -> (:+:) f g a
replace (Left Key f
a) a
v (L1 f a
fa) = f a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
a a
v f a
fa)
replace (Right Key g
b) a
v (R1 g a
fb) = g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (Key g -> a -> g a -> g a
forall a. Key g -> a -> g a -> g a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key g
b a
v g a
fb)
replace Key (f :+: g)
_ a
_ (:+:) f g a
x = (:+:) f g a
x
instance (Adjustable f, Adjustable g) => Adjustable (f :*: g) where
adjust :: forall a. (a -> a) -> Key (f :*: g) -> (:*:) f g a -> (:*:) f g a
adjust a -> a
h (Left Key f
fk) (f a
fa :*: g a
ga) = (a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
h Key f
fk f a
fa f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g a
ga
adjust a -> a
h (Right Key g
gk) (f a
fa :*: g a
ga) = f a
fa f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: (a -> a) -> Key g -> g a -> g a
forall a. (a -> a) -> Key g -> g a -> g a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
h Key g
gk g a
ga
replace :: forall a. Key (f :*: g) -> a -> (:*:) f g a -> (:*:) f g a
replace (Left Key f
fk) a
a (f a
fa :*: g a
ga) = Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
fk a
a f a
fa f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g a
ga
replace (Right Key g
gk) a
a (f a
fa :*: g a
ga) = f a
fa f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: Key g -> a -> g a -> g a
forall a. Key g -> a -> g a -> g a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key g
gk a
a g a
ga
instance (Adjustable f, Adjustable g) => Adjustable (g :.: f) where
adjust :: forall a. (a -> a) -> Key (g :.: f) -> (:.:) g f a -> (:.:) g f a
adjust a -> a
h (Key g
gk,Key f
fk) = (g (f a) -> g (f a)) -> (:.:) g f a -> (:.:) g f a
forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a'.
(g (f a) -> g' (f' a')) -> (:.:) g f a -> (:.:) g' f' a'
inComp ((f a -> f a) -> Key g -> g (f a) -> g (f a)
forall a. (a -> a) -> Key g -> g a -> g a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust ((a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
h Key f
fk) Key g
gk)
replace :: forall a. Key (g :.: f) -> a -> (:.:) g f a -> (:.:) g f a
replace (Key g
gk,Key f
fk) a
a = (g (f a) -> g (f a)) -> (:.:) g f a -> (:.:) g f a
forall (g :: * -> *) (f :: * -> *) a (g' :: * -> *) (f' :: * -> *)
a'.
(g (f a) -> g' (f' a')) -> (:.:) g f a -> (:.:) g' f' a'
inComp ((f a -> f a) -> Key g -> g (f a) -> g (f a)
forall a. (a -> a) -> Key g -> g a -> g a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust (Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
fk a
a) Key g
gk)
class Foldable t => FoldableWithKey t where
toKeyedList :: t a -> [(Key t, a)]
toKeyedList = (Key t -> a -> [(Key t, a)] -> [(Key t, a)])
-> [(Key t, a)] -> t a -> [(Key t, a)]
forall a b. (Key t -> a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey (\Key t
k a
v [(Key t, a)]
t -> (Key t
k,a
v)(Key t, a) -> [(Key t, a)] -> [(Key t, a)]
forall a. a -> [a] -> [a]
:[(Key t, a)]
t) []
foldMapWithKey :: Monoid m => (Key t -> a -> m) -> t a -> m
foldMapWithKey Key t -> a -> m
f = (Key t -> a -> m -> m) -> m -> t a -> m
forall a b. (Key t -> a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey (\Key t
k a
v -> m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (Key t -> a -> m
f Key t
k a
v)) m
forall a. Monoid a => a
mempty
foldrWithKey :: (Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey Key t -> a -> b -> b
f b
z t a
t = Endo b -> b -> b
forall a. Endo a -> a -> a
appEndo ((Key t -> a -> Endo b) -> t a -> Endo b
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (\Key t
k a
v -> (b -> b) -> Endo b
forall a. (a -> a) -> Endo a
Endo (Key t -> a -> b -> b
f Key t
k a
v)) t a
t) b
z
foldlWithKey :: (b -> Key t -> a -> b) -> b -> t a -> b
foldlWithKey b -> Key t -> a -> b
f b
z t a
t = Endo b -> b -> b
forall a. Endo a -> a -> a
appEndo (Dual (Endo b) -> Endo b
forall a. Dual a -> a
getDual ((Key t -> a -> Dual (Endo b)) -> t a -> Dual (Endo b)
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (\Key t
k a
a -> Endo b -> Dual (Endo b)
forall a. a -> Dual a
Dual ((b -> b) -> Endo b
forall a. (a -> a) -> Endo a
Endo (\b
b -> b -> Key t -> a -> b
f b
b Key t
k a
a))) t a
t)) b
z
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL foldMapWithKey | foldrWithKey #-}
#endif
instance FoldableWithKey f => FoldableWithKey (Free f) where
foldMapWithKey :: forall m a. Monoid m => (Key (Free f) -> a -> m) -> Free f a -> m
foldMapWithKey Key (Free f) -> a -> m
f (Pure a
a) = Key (Free f) -> a -> m
f Seq (Key f)
Key (Free f)
forall a. Seq a
Seq.empty a
a
foldMapWithKey Key (Free f) -> a -> m
f (Free f (Free f a)
as) = (Key f -> Free f a -> m) -> f (Free f a) -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Seq (Key f) -> a -> m) -> Free f a -> m
(Key (Free f) -> a -> m) -> Free f a -> m
forall m a. Monoid m => (Key (Free f) -> a -> m) -> Free f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Seq (Key f) -> a -> m) -> Free f a -> m)
-> (Key f -> Seq (Key f) -> a -> m) -> Key f -> Free f a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> m)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> m
Key (Free f) -> a -> m
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Free f a)
as
instance FoldableWithKey f => FoldableWithKey (Cofree f) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (Cofree f) -> a -> m) -> Cofree f a -> m
foldMapWithKey Key (Cofree f) -> a -> m
f (a
a :< f (Cofree f a)
as) = Key (Cofree f) -> a -> m
f Seq (Key f)
Key (Cofree f)
forall a. Seq a
Seq.empty a
a m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (Key f -> Cofree f a -> m) -> f (Cofree f a) -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Seq (Key f) -> a -> m) -> Cofree f a -> m
(Key (Cofree f) -> a -> m) -> Cofree f a -> m
forall m a.
Monoid m =>
(Key (Cofree f) -> a -> m) -> Cofree f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Seq (Key f) -> a -> m) -> Cofree f a -> m)
-> (Key f -> Seq (Key f) -> a -> m) -> Key f -> Cofree f a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> m)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> m
Key (Cofree f) -> a -> m
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Cofree f a)
as
instance FoldableWithKey (Tagged a) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (Tagged a) -> a -> m) -> Tagged a a -> m
foldMapWithKey Key (Tagged a) -> a -> m
f (Tagged a
a) = Key (Tagged a) -> a -> m
f () a
a
instance FoldableWithKey Proxy where
foldMapWithKey :: forall m a. Monoid m => (Key Proxy -> a -> m) -> Proxy a -> m
foldMapWithKey Key Proxy -> a -> m
_ Proxy a
_ = m
forall a. Monoid a => a
mempty
instance FoldableWithKey (Const e) where
foldMapWithKey :: forall m a. Monoid m => (Key (Const e) -> a -> m) -> Const e a -> m
foldMapWithKey Key (Const e) -> a -> m
_ Const e a
_ = m
forall a. Monoid a => a
mempty
instance FoldableWithKey (Constant e) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (Constant e) -> a -> m) -> Constant e a -> m
foldMapWithKey Key (Constant e) -> a -> m
_ Constant e a
_ = m
forall a. Monoid a => a
mempty
instance FoldableWithKey Tree where
foldMapWithKey :: forall m a. Monoid m => (Key Tree -> a -> m) -> Tree a -> m
foldMapWithKey Key Tree -> a -> m
f (Node a
a [Tree a]
as) = Key Tree -> a -> m
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (Key [] -> Tree a -> m) -> [Tree a] -> m
forall m a. Monoid m => (Key [] -> a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Seq Int -> a -> m) -> Tree a -> m
(Key Tree -> a -> m) -> Tree a -> m
forall m a. Monoid m => (Key Tree -> a -> m) -> Tree a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Seq Int -> a -> m) -> Tree a -> m)
-> (Int -> Seq Int -> a -> m) -> Int -> Tree a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> a -> m) -> (Seq Int -> Seq Int) -> Seq Int -> a -> m
forall a b. (a -> b) -> (Seq Int -> a) -> Seq Int -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq Int -> a -> m
Key Tree -> a -> m
f ((Seq Int -> Seq Int) -> Seq Int -> a -> m)
-> (Int -> Seq Int -> Seq Int) -> Int -> Seq Int -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>)) [Tree a]
as
instance FoldableWithKey Par1 where
foldMapWithKey :: forall m a. Monoid m => (Key Par1 -> a -> m) -> Par1 a -> m
foldMapWithKey Key Par1 -> a -> m
f (Par1 a
a) = Key Par1 -> a -> m
f () a
a
instance (FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (f :*: g) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (f :*: g) -> a -> m) -> (:*:) f g a -> m
foldMapWithKey Key (f :*: g) -> a -> m
f (f a
a :*: g a
b) = (Key f -> a -> m) -> f a -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (f :*: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (Key g -> a -> m) -> g a -> m
forall m a. Monoid m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (f :*: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (f :+: g) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (f :+: g) -> a -> m) -> (:+:) f g a -> m
foldMapWithKey Key (f :+: g) -> a -> m
f (L1 f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (f :+: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a
foldMapWithKey Key (f :+: g) -> a -> m
f (R1 g a
a) = (Key g -> a -> m) -> g a -> m
forall m a. Monoid m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (f :+: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
a
instance FoldableWithKey U1 where
foldMapWithKey :: forall m a. Monoid m => (Key U1 -> a -> m) -> U1 a -> m
foldMapWithKey Key U1 -> a -> m
_ U1 a
_ = m
forall a. Monoid a => a
mempty
instance FoldableWithKey V1 where
foldMapWithKey :: forall m a. Monoid m => (Key V1 -> a -> m) -> V1 a -> m
foldMapWithKey Key V1 -> a -> m
_ V1 a
v = V1 a
v V1 a -> m -> m
forall a b. a -> b -> b
`seq` m
forall a. HasCallStack => a
undefined
instance FoldableWithKey (K1 i c) where
foldMapWithKey :: forall m a. Monoid m => (Key (K1 i c) -> a -> m) -> K1 i c a -> m
foldMapWithKey Key (K1 i c) -> a -> m
_ K1 i c a
_ = m
forall a. Monoid a => a
mempty
instance FoldableWithKey f => FoldableWithKey (M1 i c f) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (M1 i c f) -> a -> m) -> M1 i c f a -> m
foldMapWithKey Key (M1 i c f) -> a -> m
f (M1 f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey Key f -> a -> m
Key (M1 i c f) -> a -> m
f f a
a
instance FoldableWithKey f => FoldableWithKey (Rec1 f) where
foldMapWithKey :: forall m a. Monoid m => (Key (Rec1 f) -> a -> m) -> Rec1 f a -> m
foldMapWithKey Key (Rec1 f) -> a -> m
f (Rec1 f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey Key f -> a -> m
Key (Rec1 f) -> a -> m
f f a
a
foldrWithKey' :: FoldableWithKey t => (Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey' :: forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey' Key t -> a -> b -> b
f b
z0 t a
xs = ((b -> b) -> Key t -> a -> b -> b) -> (b -> b) -> t a -> b -> b
forall b a. (b -> Key t -> a -> b) -> b -> t a -> b
forall (t :: * -> *) b a.
FoldableWithKey t =>
(b -> Key t -> a -> b) -> b -> t a -> b
foldlWithKey (b -> b) -> Key t -> a -> b -> b
f' b -> b
forall a. a -> a
id t a
xs b
z0
where f' :: (b -> b) -> Key t -> a -> b -> b
f' b -> b
k Key t
key a
x b
z = b -> b
k (b -> b) -> b -> b
forall a b. (a -> b) -> a -> b
$! Key t -> a -> b -> b
f Key t
key a
x b
z
{-# INLINE foldrWithKey' #-}
foldlWithKey' :: FoldableWithKey t => (b -> Key t -> a -> b) -> b -> t a -> b
foldlWithKey' :: forall (t :: * -> *) b a.
FoldableWithKey t =>
(b -> Key t -> a -> b) -> b -> t a -> b
foldlWithKey' b -> Key t -> a -> b
f b
z0 t a
xs = (Key t -> a -> (b -> b) -> b -> b) -> (b -> b) -> t a -> b -> b
forall a b. (Key t -> a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey Key t -> a -> (b -> b) -> b -> b
f' b -> b
forall a. a -> a
id t a
xs b
z0
where f' :: Key t -> a -> (b -> b) -> b -> b
f' Key t
key a
x b -> b
k b
z = b -> b
k (b -> b) -> b -> b
forall a b. (a -> b) -> a -> b
$! b -> Key t -> a -> b
f b
z Key t
key a
x
{-# INLINE foldlWithKey' #-}
foldrWithKeyM :: (FoldableWithKey t, Monad m) => (Key t -> a -> b -> m b) -> b -> t a -> m b
foldrWithKeyM :: forall (t :: * -> *) (m :: * -> *) a b.
(FoldableWithKey t, Monad m) =>
(Key t -> a -> b -> m b) -> b -> t a -> m b
foldrWithKeyM Key t -> a -> b -> m b
f b
z0 t a
xs = ((b -> m b) -> Key t -> a -> b -> m b)
-> (b -> m b) -> t a -> b -> m b
forall b a. (b -> Key t -> a -> b) -> b -> t a -> b
forall (t :: * -> *) b a.
FoldableWithKey t =>
(b -> Key t -> a -> b) -> b -> t a -> b
foldlWithKey (b -> m b) -> Key t -> a -> b -> m b
f' b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return t a
xs b
z0
where f' :: (b -> m b) -> Key t -> a -> b -> m b
f' b -> m b
k Key t
key a
x b
z = Key t -> a -> b -> m b
f Key t
key a
x b
z m b -> (b -> m b) -> m b
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= b -> m b
k
{-# INLINE foldrWithKeyM #-}
foldlWithKeyM :: (FoldableWithKey t, Monad m) => (b -> Key t -> a -> m b) -> b -> t a -> m b
foldlWithKeyM :: forall (t :: * -> *) (m :: * -> *) b a.
(FoldableWithKey t, Monad m) =>
(b -> Key t -> a -> m b) -> b -> t a -> m b
foldlWithKeyM b -> Key t -> a -> m b
f b
z0 t a
xs = (Key t -> a -> (b -> m b) -> b -> m b)
-> (b -> m b) -> t a -> b -> m b
forall a b. (Key t -> a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey Key t -> a -> (b -> m b) -> b -> m b
f' b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return t a
xs b
z0
where f' :: Key t -> a -> (b -> m b) -> b -> m b
f' Key t
key a
x b -> m b
k b
z = b -> Key t -> a -> m b
f b
z Key t
key a
x m b -> (b -> m b) -> m b
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= b -> m b
k
{-# INLINE foldlWithKeyM #-}
traverseWithKey_ :: (FoldableWithKey t, Applicative f) => (Key t -> a -> f b) -> t a -> f ()
traverseWithKey_ :: forall (t :: * -> *) (f :: * -> *) a b.
(FoldableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f ()
traverseWithKey_ Key t -> a -> f b
f = (Key t -> a -> f () -> f ()) -> f () -> t a -> f ()
forall a b. (Key t -> a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey ((f b -> f () -> f ()) -> (a -> f b) -> a -> f () -> f ()
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> f () -> f ()
forall a b. f a -> f b -> f b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>) ((a -> f b) -> a -> f () -> f ())
-> (Key t -> a -> f b) -> Key t -> a -> f () -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> f b
f) (() -> f ()
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
{-# INLINE traverseWithKey_ #-}
forWithKey_ :: (FoldableWithKey t, Applicative f) => t a -> (Key t -> a -> f b) -> f ()
forWithKey_ :: forall (t :: * -> *) (f :: * -> *) a b.
(FoldableWithKey t, Applicative f) =>
t a -> (Key t -> a -> f b) -> f ()
forWithKey_ = ((Key t -> a -> f b) -> t a -> f ())
-> t a -> (Key t -> a -> f b) -> f ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key t -> a -> f b) -> t a -> f ()
forall (t :: * -> *) (f :: * -> *) a b.
(FoldableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f ()
traverseWithKey_
{-# INLINE forWithKey_ #-}
mapWithKeyM_ :: (FoldableWithKey t, Monad m) => (Key t -> a -> m b) -> t a -> m ()
mapWithKeyM_ :: forall (t :: * -> *) (m :: * -> *) a b.
(FoldableWithKey t, Monad m) =>
(Key t -> a -> m b) -> t a -> m ()
mapWithKeyM_ Key t -> a -> m b
f = (Key t -> a -> m () -> m ()) -> m () -> t a -> m ()
forall a b. (Key t -> a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey ((m b -> m () -> m ()) -> (a -> m b) -> a -> m () -> m ()
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap m b -> m () -> m ()
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
(>>) ((a -> m b) -> a -> m () -> m ())
-> (Key t -> a -> m b) -> Key t -> a -> m () -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> m b
f) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
{-# INLINE mapWithKeyM_ #-}
forWithKeyM_ :: (FoldableWithKey t, Monad m) => t a -> (Key t -> a -> m b) -> m ()
forWithKeyM_ :: forall (t :: * -> *) (m :: * -> *) a b.
(FoldableWithKey t, Monad m) =>
t a -> (Key t -> a -> m b) -> m ()
forWithKeyM_ = ((Key t -> a -> m b) -> t a -> m ())
-> t a -> (Key t -> a -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key t -> a -> m b) -> t a -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(FoldableWithKey t, Monad m) =>
(Key t -> a -> m b) -> t a -> m ()
mapWithKeyM_
{-# INLINE forWithKeyM_ #-}
concatMapWithKey :: FoldableWithKey t => (Key t -> a -> [b]) -> t a -> [b]
concatMapWithKey :: forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> [b]) -> t a -> [b]
concatMapWithKey = (Key t -> a -> [b]) -> t a -> [b]
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey
{-# INLINE concatMapWithKey #-}
anyWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Bool
anyWithKey :: forall (t :: * -> *) a.
FoldableWithKey t =>
(Key t -> a -> Bool) -> t a -> Bool
anyWithKey Key t -> a -> Bool
p = Any -> Bool
getAny (Any -> Bool) -> (t a -> Any) -> t a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> Any) -> t a -> Any
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Bool -> Any) -> (a -> Bool) -> a -> Any
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Any
Any ((a -> Bool) -> a -> Any)
-> (Key t -> a -> Bool) -> Key t -> a -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> Bool
p)
{-# INLINE anyWithKey #-}
allWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Bool
allWithKey :: forall (t :: * -> *) a.
FoldableWithKey t =>
(Key t -> a -> Bool) -> t a -> Bool
allWithKey Key t -> a -> Bool
p = All -> Bool
getAll (All -> Bool) -> (t a -> All) -> t a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> All) -> t a -> All
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Bool -> All) -> (a -> Bool) -> a -> All
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> All
All ((a -> Bool) -> a -> All)
-> (Key t -> a -> Bool) -> Key t -> a -> All
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> Bool
p)
{-# INLINE allWithKey #-}
findWithKey :: FoldableWithKey t => (Key t -> a -> Bool) -> t a -> Maybe a
findWithKey :: forall (t :: * -> *) a.
FoldableWithKey t =>
(Key t -> a -> Bool) -> t a -> Maybe a
findWithKey Key t -> a -> Bool
p = First a -> Maybe a
forall a. First a -> Maybe a
Monoid.getFirst (First a -> Maybe a) -> (t a -> First a) -> t a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> First a) -> t a -> First a
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (\Key t
k a
x -> Maybe a -> First a
forall a. Maybe a -> First a
Monoid.First (if Key t -> a -> Bool
p Key t
k a
x then a -> Maybe a
forall a. a -> Maybe a
Just a
x else Maybe a
forall a. Maybe a
Nothing) )
{-# INLINE findWithKey #-}
class (Foldable1 t, FoldableWithKey t) => FoldableWithKey1 t where
foldMapWithKey1 :: Semigroup m => (Key t -> a -> m) -> t a -> m
instance FoldableWithKey1 f => FoldableWithKey1 (Cofree f) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Cofree f) -> a -> m) -> Cofree f a -> m
foldMapWithKey1 Key (Cofree f) -> a -> m
f (a
a :< f (Cofree f a)
as) = Key (Cofree f) -> a -> m
f Seq (Key f)
Key (Cofree f)
forall a. Seq a
Seq.empty a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (Key f -> Cofree f a -> m) -> f (Cofree f a) -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Seq (Key f) -> a -> m) -> Cofree f a -> m
(Key (Cofree f) -> a -> m) -> Cofree f a -> m
forall m a.
Semigroup m =>
(Key (Cofree f) -> a -> m) -> Cofree f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Seq (Key f) -> a -> m) -> Cofree f a -> m)
-> (Key f -> Seq (Key f) -> a -> m) -> Key f -> Cofree f a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> m)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> m
Key (Cofree f) -> a -> m
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Cofree f a)
as
instance FoldableWithKey1 Tree where
foldMapWithKey1 :: forall m a. Semigroup m => (Key Tree -> a -> m) -> Tree a -> m
foldMapWithKey1 Key Tree -> a -> m
f (Node a
a []) = Key Tree -> a -> m
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a
foldMapWithKey1 Key Tree -> a -> m
f (Node a
a (Tree a
x:[Tree a]
xs)) = Key Tree -> a -> m
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (Key NonEmpty -> Tree a -> m) -> NonEmpty (Tree a) -> m
forall m a.
Semigroup m =>
(Key NonEmpty -> a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Seq Int -> a -> m) -> Tree a -> m
(Key Tree -> a -> m) -> Tree a -> m
forall m a. Semigroup m => (Key Tree -> a -> m) -> Tree a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Seq Int -> a -> m) -> Tree a -> m)
-> (Int -> Seq Int -> a -> m) -> Int -> Tree a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> a -> m) -> (Seq Int -> Seq Int) -> Seq Int -> a -> m
forall a b. (a -> b) -> (Seq Int -> a) -> Seq Int -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq Int -> a -> m
Key Tree -> a -> m
f ((Seq Int -> Seq Int) -> Seq Int -> a -> m)
-> (Int -> Seq Int -> Seq Int) -> Int -> Seq Int -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>)) (Tree a
xTree a -> [Tree a] -> NonEmpty (Tree a)
forall a. a -> [a] -> NonEmpty a
:|[Tree a]
xs)
instance FoldableWithKey1 f => FoldableWithKey1 (Free f) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Free f) -> a -> m) -> Free f a -> m
foldMapWithKey1 Key (Free f) -> a -> m
f (Pure a
a) = Key (Free f) -> a -> m
f Seq (Key f)
Key (Free f)
forall a. Seq a
Seq.empty a
a
foldMapWithKey1 Key (Free f) -> a -> m
f (Free f (Free f a)
as) = (Key f -> Free f a -> m) -> f (Free f a) -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Seq (Key f) -> a -> m) -> Free f a -> m
(Key (Free f) -> a -> m) -> Free f a -> m
forall m a.
Semigroup m =>
(Key (Free f) -> a -> m) -> Free f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Seq (Key f) -> a -> m) -> Free f a -> m)
-> (Key f -> Seq (Key f) -> a -> m) -> Key f -> Free f a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> m)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> m
Key (Free f) -> a -> m
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> m)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Free f a)
as
instance FoldableWithKey1 (Tagged a) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Tagged a) -> a -> m) -> Tagged a a -> m
foldMapWithKey1 Key (Tagged a) -> a -> m
f (Tagged a
a) = Key (Tagged a) -> a -> m
f () a
a
instance (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (f :*: g) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (f :*: g) -> a -> m) -> (:*:) f g a -> m
foldMapWithKey1 Key (f :*: g) -> a -> m
f (f a
a :*: g a
b) = (Key f -> a -> m) -> f a -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (f :*: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (Key g -> a -> m) -> g a -> m
forall m a. Semigroup m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (f :*: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (f :+: g) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (f :+: g) -> a -> m) -> (:+:) f g a -> m
foldMapWithKey1 Key (f :+: g) -> a -> m
f (L1 f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (f :+: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a
foldMapWithKey1 Key (f :+: g) -> a -> m
f (R1 g a
a) = (Key g -> a -> m) -> g a -> m
forall m a. Semigroup m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (f :+: g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
a
instance FoldableWithKey1 V1 where
foldMapWithKey1 :: forall m a. Semigroup m => (Key V1 -> a -> m) -> V1 a -> m
foldMapWithKey1 Key V1 -> a -> m
_ V1 a
v = V1 a
v V1 a -> m -> m
forall a b. a -> b -> b
`seq` m
forall a. HasCallStack => a
undefined
instance FoldableWithKey1 Par1 where
foldMapWithKey1 :: forall m a. Semigroup m => (Key Par1 -> a -> m) -> Par1 a -> m
foldMapWithKey1 Key Par1 -> a -> m
f (Par1 a
a) = Key Par1 -> a -> m
f () a
a
instance FoldableWithKey1 f => FoldableWithKey1 (M1 i c f) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (M1 i c f) -> a -> m) -> M1 i c f a -> m
foldMapWithKey1 Key (M1 i c f) -> a -> m
f (M1 f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 Key f -> a -> m
Key (M1 i c f) -> a -> m
f f a
a
instance FoldableWithKey1 f => FoldableWithKey1 (Rec1 f) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Rec1 f) -> a -> m) -> Rec1 f a -> m
foldMapWithKey1 Key (Rec1 f) -> a -> m
f (Rec1 f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 Key f -> a -> m
Key (Rec1 f) -> a -> m
f f a
a
newtype Act f a = Act { forall (f :: * -> *) a. Act f a -> f a
getAct :: f a }
instance Apply f => Semigroup (Act f a) where
Act f a
a <> :: Act f a -> Act f a -> Act f a
<> Act f a
b = f a -> Act f a
forall (f :: * -> *) a. f a -> Act f a
Act (f a
a f a -> f a -> f a
forall a b. f a -> f b -> f b
forall (f :: * -> *) a b. Apply f => f a -> f b -> f b
.> f a
b)
instance Functor f => Functor (Act f) where
fmap :: forall a b. (a -> b) -> Act f a -> Act f b
fmap a -> b
f (Act f a
a) = f b -> Act f b
forall (f :: * -> *) a. f a -> Act f a
Act (a -> b
f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
a)
a
b <$ :: forall a b. a -> Act f b -> Act f a
<$ Act f b
a = f a -> Act f a
forall (f :: * -> *) a. f a -> Act f a
Act (a
b a -> f b -> f a
forall a b. a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ f b
a)
traverseWithKey1_ :: (FoldableWithKey1 t, Apply f) => (Key t -> a -> f b) -> t a -> f ()
traverseWithKey1_ :: forall (t :: * -> *) (f :: * -> *) a b.
(FoldableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f ()
traverseWithKey1_ Key t -> a -> f b
f = () -> f b -> f ()
forall a b. a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
(<$) () (f b -> f ()) -> (t a -> f b) -> t a -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Act f b -> f b
forall (f :: * -> *) a. Act f a -> f a
getAct (Act f b -> f b) -> (t a -> Act f b) -> t a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> Act f b) -> t a -> Act f b
forall m a. Semigroup m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((f b -> Act f b) -> (a -> f b) -> a -> Act f b
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> Act f b
forall (f :: * -> *) a. f a -> Act f a
Act ((a -> f b) -> a -> Act f b)
-> (Key t -> a -> f b) -> Key t -> a -> Act f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> f b
f)
{-# INLINE traverseWithKey1_ #-}
forWithKey1_ :: (FoldableWithKey1 t, Apply f) => t a -> (Key t -> a -> f b) -> f ()
forWithKey1_ :: forall (t :: * -> *) (f :: * -> *) a b.
(FoldableWithKey1 t, Apply f) =>
t a -> (Key t -> a -> f b) -> f ()
forWithKey1_ = ((Key t -> a -> f b) -> t a -> f ())
-> t a -> (Key t -> a -> f b) -> f ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key t -> a -> f b) -> t a -> f ()
forall (t :: * -> *) (f :: * -> *) a b.
(FoldableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f ()
traverseWithKey1_
{-# INLINE forWithKey1_ #-}
foldMapWithKeyDefault1 :: (FoldableWithKey1 t, Monoid m) => (Key t -> a -> m) -> t a -> m
foldMapWithKeyDefault1 :: forall (t :: * -> *) m a.
(FoldableWithKey1 t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKeyDefault1 Key t -> a -> m
f = WrappedMonoid m -> m
forall m. WrappedMonoid m -> m
unwrapMonoid (WrappedMonoid m -> m) -> (t a -> WrappedMonoid m) -> t a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> WrappedMonoid m) -> t a -> WrappedMonoid m
forall m a. Monoid m => (Key t -> a -> m) -> t a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((m -> WrappedMonoid m) -> (a -> m) -> a -> WrappedMonoid m
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap m -> WrappedMonoid m
forall m. m -> WrappedMonoid m
WrapMonoid ((a -> m) -> a -> WrappedMonoid m)
-> (Key t -> a -> m) -> Key t -> a -> WrappedMonoid m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> m
f)
{-# INLINE foldMapWithKeyDefault1 #-}
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)
mapWithKeyM Key t -> a -> m b
f = WrappedMonad m (t b) -> m (t b)
forall (m :: * -> *) a. WrappedMonad m a -> m a
unwrapMonad (WrappedMonad m (t b) -> m (t b))
-> (t a -> WrappedMonad m (t b)) -> t a -> m (t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> WrappedMonad m b) -> t a -> WrappedMonad m (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey ((m b -> WrappedMonad m b) -> (a -> m b) -> a -> WrappedMonad m b
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap m b -> WrappedMonad m b
forall (m :: * -> *) a. m a -> WrappedMonad m a
WrapMonad ((a -> m b) -> a -> WrappedMonad m b)
-> (Key t -> a -> m b) -> Key t -> a -> WrappedMonad m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> m b
f)
instance TraversableWithKey (Tagged a) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Tagged a) -> a -> f b) -> Tagged a a -> f (Tagged a b)
traverseWithKey Key (Tagged a) -> a -> f b
f (Tagged a
a) = b -> Tagged a b
forall {k} (s :: k) b. b -> Tagged s b
Tagged (b -> Tagged a b) -> f b -> f (Tagged a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Tagged a) -> a -> f b
f () a
a
instance TraversableWithKey Proxy where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key Proxy -> a -> f b) -> Proxy a -> f (Proxy b)
traverseWithKey Key Proxy -> a -> f b
_ Proxy a
_ = Proxy b -> f (Proxy b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy b
forall {k} (t :: k). Proxy t
Proxy
instance TraversableWithKey (Const e) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Const e) -> a -> f b) -> Const e a -> f (Const e b)
traverseWithKey Key (Const e) -> a -> f b
_ (Const e
a) = Const e b -> f (Const e b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (e -> Const e b
forall {k} a (b :: k). a -> Const a b
Const e
a)
instance TraversableWithKey (Constant e) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Constant e) -> a -> f b) -> Constant e a -> f (Constant e b)
traverseWithKey Key (Constant e) -> a -> f b
_ (Constant e
a) = Constant e b -> f (Constant e b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (e -> Constant e b
forall {k} a (b :: k). a -> Constant a b
Constant e
a)
instance TraversableWithKey f => TraversableWithKey (Cofree f) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
traverseWithKey Key (Cofree f) -> a -> f b
f (a
a :< f (Cofree f a)
as) = b -> f (Cofree f b) -> Cofree f b
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
(:<) (b -> f (Cofree f b) -> Cofree f b)
-> f b -> f (f (Cofree f b) -> Cofree f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Cofree f) -> a -> f b
f Seq (Key f)
Key (Cofree f)
forall a. Seq a
Seq.empty a
a f (f (Cofree f b) -> Cofree f b)
-> f (f (Cofree f b)) -> f (Cofree f b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Key f -> Cofree f a -> f (Cofree f b))
-> f (Cofree f a) -> f (f (Cofree f b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey ((Seq (Key f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
(Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
traverseWithKey ((Seq (Key f) -> a -> f b) -> Cofree f a -> f (Cofree f b))
-> (Key f -> Seq (Key f) -> a -> f b)
-> Key f
-> Cofree f a
-> f (Cofree f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> f b)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> f b
Key (Cofree f) -> a -> f b
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Cofree f a)
as
instance TraversableWithKey Tree where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key Tree -> a -> f b) -> Tree a -> f (Tree b)
traverseWithKey Key Tree -> a -> f b
f (Node a
a [Tree a]
as) = b -> [Tree b] -> Tree b
forall a. a -> [Tree a] -> Tree a
Node (b -> [Tree b] -> Tree b) -> f b -> f ([Tree b] -> Tree b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Tree -> a -> f b
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a f ([Tree b] -> Tree b) -> f [Tree b] -> f (Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Key [] -> Tree a -> f (Tree b)) -> [Tree a] -> f [Tree b]
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key [] -> a -> f b) -> [a] -> f [b]
traverseWithKey ((Seq Int -> a -> f b) -> Tree a -> f (Tree b)
(Key Tree -> a -> f b) -> Tree a -> f (Tree b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key Tree -> a -> f b) -> Tree a -> f (Tree b)
traverseWithKey ((Seq Int -> a -> f b) -> Tree a -> f (Tree b))
-> (Int -> Seq Int -> a -> f b) -> Int -> Tree a -> f (Tree b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> a -> f b)
-> (Seq Int -> Seq Int) -> Seq Int -> a -> f b
forall a b. (a -> b) -> (Seq Int -> a) -> Seq Int -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq Int -> a -> f b
Key Tree -> a -> f b
f ((Seq Int -> Seq Int) -> Seq Int -> a -> f b)
-> (Int -> Seq Int -> Seq Int) -> Int -> Seq Int -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>)) [Tree a]
as
instance TraversableWithKey f => TraversableWithKey (Free f) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Free f) -> a -> f b) -> Free f a -> f (Free f b)
traverseWithKey Key (Free f) -> a -> f b
f (Pure a
a) = b -> Free f b
forall (f :: * -> *) a. a -> Free f a
Pure (b -> Free f b) -> f b -> f (Free f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Free f) -> a -> f b
f Seq (Key f)
Key (Free f)
forall a. Seq a
Seq.empty a
a
traverseWithKey Key (Free f) -> a -> f b
f (Free f (Free f a)
as) = f (Free f b) -> Free f b
forall (f :: * -> *) a. f (Free f a) -> Free f a
Free (f (Free f b) -> Free f b) -> f (f (Free f b)) -> f (Free f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> Free f a -> f (Free f b))
-> f (Free f a) -> f (f (Free f b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey ((Seq (Key f) -> a -> f b) -> Free f a -> f (Free f b)
(Key (Free f) -> a -> f b) -> Free f a -> f (Free f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key (Free f) -> a -> f b) -> Free f a -> f (Free f b)
traverseWithKey ((Seq (Key f) -> a -> f b) -> Free f a -> f (Free f b))
-> (Key f -> Seq (Key f) -> a -> f b)
-> Key f
-> Free f a
-> f (Free f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> f b)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> f b
Key (Free f) -> a -> f b
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Free f a)
as
instance (TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (f :*: g) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (f :*: g) -> a -> f b) -> (:*:) f g a -> f ((:*:) f g b)
traverseWithKey Key (f :*: g) -> a -> f b
f (f a
a :*: g a
b) = f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (f b -> g b -> (:*:) f g b) -> f (f b) -> f (g b -> (:*:) f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (f :*: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a f (g b -> (:*:) f g b) -> f (g b) -> f ((:*:) f g b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (f :*: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (f :+: g) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (f :+: g) -> a -> f b) -> (:+:) f g a -> f ((:+:) f g b)
traverseWithKey Key (f :+: g) -> a -> f b
f (L1 f a
as) = f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (f b -> (:+:) f g b) -> f (f b) -> f ((:+:) f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (f :+: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
as
traverseWithKey Key (f :+: g) -> a -> f b
f (R1 g a
bs) = g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (g b -> (:+:) f g b) -> f (g b) -> f ((:+:) f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (f :+: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
bs
instance TraversableWithKey Par1 where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key Par1 -> a -> f b) -> Par1 a -> f (Par1 b)
traverseWithKey Key Par1 -> a -> f b
f (Par1 a
a) = b -> Par1 b
forall p. p -> Par1 p
Par1 (b -> Par1 b) -> f b -> f (Par1 b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Par1 -> a -> f b
f () a
a
instance TraversableWithKey U1 where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key U1 -> a -> f b) -> U1 a -> f (U1 b)
traverseWithKey Key U1 -> a -> f b
_ U1 a
U1 = U1 b -> f (U1 b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 b
forall k (p :: k). U1 p
U1
instance TraversableWithKey V1 where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key V1 -> a -> f b) -> V1 a -> f (V1 b)
traverseWithKey Key V1 -> a -> f b
_ V1 a
v = V1 a
v V1 a -> f (V1 b) -> f (V1 b)
forall a b. a -> b -> b
`seq` f (V1 b)
forall a. HasCallStack => a
undefined
instance TraversableWithKey (K1 i c) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (K1 i c) -> a -> f b) -> K1 i c a -> f (K1 i c b)
traverseWithKey Key (K1 i c) -> a -> f b
_ (K1 c
p) = K1 i c b -> f (K1 i c b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (c -> K1 i c b
forall k i c (p :: k). c -> K1 i c p
K1 c
p)
instance TraversableWithKey f => TraversableWithKey (Rec1 f) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Rec1 f) -> a -> f b) -> Rec1 f a -> f (Rec1 f b)
traverseWithKey Key (Rec1 f) -> a -> f b
f (Rec1 f a
a) = f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 (f b -> Rec1 f b) -> f (f b) -> f (Rec1 f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey Key f -> a -> f b
Key (Rec1 f) -> a -> f b
f f a
a
instance TraversableWithKey f => TraversableWithKey (M1 i c f) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (M1 i c f) -> a -> f b) -> M1 i c f a -> f (M1 i c f b)
traverseWithKey Key (M1 i c f) -> a -> f b
f (M1 f a
a) = f b -> M1 i c f b
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f b -> M1 i c f b) -> f (f b) -> f (M1 i c f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey Key f -> a -> f b
Key (M1 i c f) -> a -> f b
f f a
a
forWithKey :: (TraversableWithKey t, Applicative f) => t a -> (Key t -> a -> f b) -> f (t b)
forWithKey :: forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
t a -> (Key t -> a -> f b) -> f (t b)
forWithKey = ((Key t -> a -> f b) -> t a -> f (t b))
-> t a -> (Key t -> a -> f b) -> f (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key t -> a -> f b) -> t a -> f (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey
{-# INLINE forWithKey #-}
forWithKeyM :: (TraversableWithKey t, Monad m) => t a -> (Key t -> a -> m b) -> m (t b)
forWithKeyM :: forall (t :: * -> *) (m :: * -> *) a b.
(TraversableWithKey t, Monad m) =>
t a -> (Key t -> a -> m b) -> m (t b)
forWithKeyM = ((Key t -> a -> m b) -> t a -> m (t b))
-> t a -> (Key t -> a -> m b) -> m (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key t -> a -> m b) -> t a -> m (t b)
forall (t :: * -> *) (m :: * -> *) a b.
(TraversableWithKey t, Monad m) =>
(Key t -> a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(Key t -> a -> m b) -> t a -> m (t b)
mapWithKeyM
{-# INLINE forWithKeyM #-}
newtype StateL s a = StateL { forall s a. StateL s a -> s -> (s, a)
runStateL :: s -> (s, a) }
instance Functor (StateL s) where
fmap :: forall a b. (a -> b) -> StateL s a -> StateL s b
fmap a -> b
f (StateL s -> (s, a)
k) = (s -> (s, b)) -> StateL s b
forall s a. (s -> (s, a)) -> StateL s a
StateL ((s -> (s, b)) -> StateL s b) -> (s -> (s, b)) -> StateL s b
forall a b. (a -> b) -> a -> b
$ \ s
s ->
let (s
s', a
v) = s -> (s, a)
k s
s in (s
s', a -> b
f a
v)
instance Applicative (StateL s) where
pure :: forall a. a -> StateL s a
pure a
x = (s -> (s, a)) -> StateL s a
forall s a. (s -> (s, a)) -> StateL s a
StateL (\ s
s -> (s
s, a
x))
StateL s -> (s, a -> b)
kf <*> :: forall a b. StateL s (a -> b) -> StateL s a -> StateL s b
<*> StateL s -> (s, a)
kv = (s -> (s, b)) -> StateL s b
forall s a. (s -> (s, a)) -> StateL s a
StateL ((s -> (s, b)) -> StateL s b) -> (s -> (s, b)) -> StateL s b
forall a b. (a -> b) -> a -> b
$ \ s
s ->
let (s
s', a -> b
f) = s -> (s, a -> b)
kf s
s
(s
s'', a
v) = s -> (s, a)
kv s
s'
in (s
s'', a -> b
f a
v)
mapAccumWithKeyL :: TraversableWithKey t => (Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumWithKeyL :: forall (t :: * -> *) a b c.
TraversableWithKey t =>
(Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumWithKeyL Key t -> a -> b -> (a, c)
f a
s t b
t = StateL a (t c) -> a -> (a, t c)
forall s a. StateL s a -> s -> (s, a)
runStateL ((Key t -> b -> StateL a c) -> t b -> StateL a (t c)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey (\Key t
k b
b -> (a -> (a, c)) -> StateL a c
forall s a. (s -> (s, a)) -> StateL s a
StateL (\a
a -> Key t -> a -> b -> (a, c)
f Key t
k a
a b
b)) t b
t) a
s
{-# INLINE mapAccumWithKeyL #-}
newtype StateR s a = StateR { forall s a. StateR s a -> s -> (s, a)
runStateR :: s -> (s, a) }
instance Functor (StateR s) where
fmap :: forall a b. (a -> b) -> StateR s a -> StateR s b
fmap a -> b
f (StateR s -> (s, a)
k) = (s -> (s, b)) -> StateR s b
forall s a. (s -> (s, a)) -> StateR s a
StateR ((s -> (s, b)) -> StateR s b) -> (s -> (s, b)) -> StateR s b
forall a b. (a -> b) -> a -> b
$ \ s
s ->
let (s
s', a
v) = s -> (s, a)
k s
s in (s
s', a -> b
f a
v)
instance Applicative (StateR s) where
pure :: forall a. a -> StateR s a
pure a
x = (s -> (s, a)) -> StateR s a
forall s a. (s -> (s, a)) -> StateR s a
StateR (\ s
s -> (s
s, a
x))
StateR s -> (s, a -> b)
kf <*> :: forall a b. StateR s (a -> b) -> StateR s a -> StateR s b
<*> StateR s -> (s, a)
kv = (s -> (s, b)) -> StateR s b
forall s a. (s -> (s, a)) -> StateR s a
StateR ((s -> (s, b)) -> StateR s b) -> (s -> (s, b)) -> StateR s b
forall a b. (a -> b) -> a -> b
$ \ s
s ->
let (s
s', a
v) = s -> (s, a)
kv s
s
(s
s'', a -> b
f) = s -> (s, a -> b)
kf s
s'
in (s
s'', a -> b
f a
v)
mapAccumWithKeyR :: TraversableWithKey t => (Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumWithKeyR :: forall (t :: * -> *) a b c.
TraversableWithKey t =>
(Key t -> a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumWithKeyR Key t -> a -> b -> (a, c)
f a
s t b
t = StateR a (t c) -> a -> (a, t c)
forall s a. StateR s a -> s -> (s, a)
runStateR ((Key t -> b -> StateR a c) -> t b -> StateR a (t c)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey (\Key t
k b
b -> (a -> (a, c)) -> StateR a c
forall s a. (s -> (s, a)) -> StateR s a
StateR (\a
a -> Key t -> a -> b -> (a, c)
f Key t
k a
a b
b)) t b
t) a
s
{-# INLINE mapAccumWithKeyR #-}
mapWithKeyDefault :: TraversableWithKey t => (Key t -> a -> b) -> t a -> t b
mapWithKeyDefault :: forall (t :: * -> *) a b.
TraversableWithKey t =>
(Key t -> a -> b) -> t a -> t b
mapWithKeyDefault Key t -> a -> b
f = Identity (t b) -> t b
forall a. Identity a -> a
runIdentity (Identity (t b) -> t b) -> (t a -> Identity (t b)) -> t a -> t b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> Identity b) -> t a -> Identity (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey ((b -> Identity b) -> (a -> b) -> a -> Identity b
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Identity b
forall a. a -> Identity a
Identity ((a -> b) -> a -> Identity b)
-> (Key t -> a -> b) -> Key t -> a -> Identity b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> b
f)
{-# INLINE mapWithKeyDefault #-}
foldMapWithKeyDefault :: (TraversableWithKey t, Monoid m) => (Key t -> a -> m) -> t a -> m
foldMapWithKeyDefault :: forall (t :: * -> *) m a.
(TraversableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKeyDefault Key t -> a -> m
f = Const m (t Any) -> m
forall {k} a (b :: k). Const a b -> a
getConst (Const m (t Any) -> m) -> (t a -> Const m (t Any)) -> t a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> Const m Any) -> t a -> Const m (t Any)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey ((m -> Const m Any) -> (a -> m) -> a -> Const m Any
forall a b. (a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap m -> Const m Any
forall {k} a (b :: k). a -> Const a b
Const ((a -> m) -> a -> Const m Any)
-> (Key t -> a -> m) -> Key t -> a -> Const m Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> m
f)
{-# INLINE foldMapWithKeyDefault #-}
class (Traversable1 t, FoldableWithKey1 t, TraversableWithKey t) => TraversableWithKey1 t where
traverseWithKey1 :: Apply f => (Key t -> a -> f b) -> t a -> f (t b)
instance TraversableWithKey1 (Tagged a) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Tagged a) -> a -> f b) -> Tagged a a -> f (Tagged a b)
traverseWithKey1 Key (Tagged a) -> a -> f b
f (Tagged a
a) = b -> Tagged a b
forall {k} (s :: k) b. b -> Tagged s b
Tagged (b -> Tagged a b) -> f b -> f (Tagged a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Tagged a) -> a -> f b
f () a
a
instance TraversableWithKey1 f => TraversableWithKey1 (Cofree f) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
traverseWithKey1 Key (Cofree f) -> a -> f b
f (a
a :< f (Cofree f a)
as) = b -> f (Cofree f b) -> Cofree f b
forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
(:<) (b -> f (Cofree f b) -> Cofree f b)
-> f b -> f (f (Cofree f b) -> Cofree f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Cofree f) -> a -> f b
f Seq (Key f)
Key (Cofree f)
forall a. Seq a
Seq.empty a
a f (f (Cofree f b) -> Cofree f b)
-> f (f (Cofree f b)) -> f (Cofree f b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (Key f -> Cofree f a -> f (Cofree f b))
-> f (Cofree f a) -> f (f (Cofree f b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 ((Seq (Key f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
(Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key (Cofree f) -> a -> f b) -> Cofree f a -> f (Cofree f b)
traverseWithKey1 ((Seq (Key f) -> a -> f b) -> Cofree f a -> f (Cofree f b))
-> (Key f -> Seq (Key f) -> a -> f b)
-> Key f
-> Cofree f a
-> f (Cofree f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> f b)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> f b
Key (Cofree f) -> a -> f b
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Cofree f a)
as
instance TraversableWithKey1 Tree where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key Tree -> a -> f b) -> Tree a -> f (Tree b)
traverseWithKey1 Key Tree -> a -> f b
f (Node a
a []) = (b -> [Tree b] -> Tree b
forall a. a -> [Tree a] -> Tree a
`Node`[]) (b -> Tree b) -> f b -> f (Tree b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Tree -> a -> f b
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a
traverseWithKey1 Key Tree -> a -> f b
f (Node a
a (Tree a
x:[Tree a]
xs)) = (\b
b (Tree b
y:|[Tree b]
ys) -> b -> [Tree b] -> Tree b
forall a. a -> [Tree a] -> Tree a
Node b
b (Tree b
yTree b -> [Tree b] -> [Tree b]
forall a. a -> [a] -> [a]
:[Tree b]
ys)) (b -> NonEmpty (Tree b) -> Tree b)
-> f b -> f (NonEmpty (Tree b) -> Tree b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Tree -> a -> f b
f Seq Int
Key Tree
forall a. Seq a
Seq.empty a
a f (NonEmpty (Tree b) -> Tree b)
-> f (NonEmpty (Tree b)) -> f (Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (Key NonEmpty -> Tree a -> f (Tree b))
-> NonEmpty (Tree a) -> f (NonEmpty (Tree b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverseWithKey1 ((Seq Int -> a -> f b) -> Tree a -> f (Tree b)
(Key Tree -> a -> f b) -> Tree a -> f (Tree b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key Tree -> a -> f b) -> Tree a -> f (Tree b)
traverseWithKey1 ((Seq Int -> a -> f b) -> Tree a -> f (Tree b))
-> (Int -> Seq Int -> a -> f b) -> Int -> Tree a -> f (Tree b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> a -> f b)
-> (Seq Int -> Seq Int) -> Seq Int -> a -> f b
forall a b. (a -> b) -> (Seq Int -> a) -> Seq Int -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq Int -> a -> f b
Key Tree -> a -> f b
f ((Seq Int -> Seq Int) -> Seq Int -> a -> f b)
-> (Int -> Seq Int -> Seq Int) -> Int -> Seq Int -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>)) (Tree a
xTree a -> [Tree a] -> NonEmpty (Tree a)
forall a. a -> [a] -> NonEmpty a
:|[Tree a]
xs)
instance TraversableWithKey1 f => TraversableWithKey1 (Free f) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Free f) -> a -> f b) -> Free f a -> f (Free f b)
traverseWithKey1 Key (Free f) -> a -> f b
f (Pure a
a) = b -> Free f b
forall (f :: * -> *) a. a -> Free f a
Pure (b -> Free f b) -> f b -> f (Free f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Free f) -> a -> f b
f Seq (Key f)
Key (Free f)
forall a. Seq a
Seq.empty a
a
traverseWithKey1 Key (Free f) -> a -> f b
f (Free f (Free f a)
as) = f (Free f b) -> Free f b
forall (f :: * -> *) a. f (Free f a) -> Free f a
Free (f (Free f b) -> Free f b) -> f (f (Free f b)) -> f (Free f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> Free f a -> f (Free f b))
-> f (Free f a) -> f (f (Free f b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 ((Seq (Key f) -> a -> f b) -> Free f a -> f (Free f b)
(Key (Free f) -> a -> f b) -> Free f a -> f (Free f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key (Free f) -> a -> f b) -> Free f a -> f (Free f b)
traverseWithKey1 ((Seq (Key f) -> a -> f b) -> Free f a -> f (Free f b))
-> (Key f -> Seq (Key f) -> a -> f b)
-> Key f
-> Free f a
-> f (Free f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> a -> f b)
-> (Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b
forall a b. (a -> b) -> (Seq (Key f) -> a) -> Seq (Key f) -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq (Key f) -> a -> f b
Key (Free f) -> a -> f b
f ((Seq (Key f) -> Seq (Key f)) -> Seq (Key f) -> a -> f b)
-> (Key f -> Seq (Key f) -> Seq (Key f))
-> Key f
-> Seq (Key f)
-> a
-> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Seq (Key f) -> Key f -> Seq (Key f))
-> Key f -> Seq (Key f) -> Seq (Key f)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq (Key f) -> Key f -> Seq (Key f)
forall a. Seq a -> a -> Seq a
(|>)) f (Free f a)
as
instance TraversableWithKey1 Par1 where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key Par1 -> a -> f b) -> Par1 a -> f (Par1 b)
traverseWithKey1 Key Par1 -> a -> f b
f (Par1 a
a) = b -> Par1 b
forall p. p -> Par1 p
Par1 (b -> Par1 b) -> f b -> f (Par1 b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Par1 -> a -> f b
f () a
a
instance TraversableWithKey1 f => TraversableWithKey1 (Rec1 f) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Rec1 f) -> a -> f b) -> Rec1 f a -> f (Rec1 f b)
traverseWithKey1 Key (Rec1 f) -> a -> f b
f (Rec1 f a
a) = f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1 (f b -> Rec1 f b) -> f (f b) -> f (Rec1 f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 Key f -> a -> f b
Key (Rec1 f) -> a -> f b
f f a
a
instance TraversableWithKey1 f => TraversableWithKey1 (M1 i c f) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (M1 i c f) -> a -> f b) -> M1 i c f a -> f (M1 i c f b)
traverseWithKey1 Key (M1 i c f) -> a -> f b
f (M1 f a
a) = f b -> M1 i c f b
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (f b -> M1 i c f b) -> f (f b) -> f (M1 i c f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 Key f -> a -> f b
Key (M1 i c f) -> a -> f b
f f a
a
instance TraversableWithKey1 V1 where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key V1 -> a -> f b) -> V1 a -> f (V1 b)
traverseWithKey1 Key V1 -> a -> f b
_ V1 a
v = V1 a
v V1 a -> f (V1 b) -> f (V1 b)
forall a b. a -> b -> b
`seq` f (V1 b)
forall a. HasCallStack => a
undefined
instance (TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (f :*: g) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (f :*: g) -> a -> f b) -> (:*:) f g a -> f ((:*:) f g b)
traverseWithKey1 Key (f :*: g) -> a -> f b
f (f a
a :*: g a
b) = f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (f b -> g b -> (:*:) f g b) -> f (f b) -> f (g b -> (:*:) f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (f :*: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a f (g b -> (:*:) f g b) -> f (g b) -> f ((:*:) f g b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (f :*: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (f :+: g) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (f :+: g) -> a -> f b) -> (:+:) f g a -> f ((:+:) f g b)
traverseWithKey1 Key (f :+: g) -> a -> f b
f (L1 f a
as) = f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (f b -> (:+:) f g b) -> f (f b) -> f ((:+:) f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (f :+: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
as
traverseWithKey1 Key (f :+: g) -> a -> f b
f (R1 g a
bs) = g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (g b -> (:+:) f g b) -> f (g b) -> f ((:+:) f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (f :+: g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
bs
foldMapWithKey1Default :: (TraversableWithKey1 t, Semigroup m) => (Key t -> a -> m) -> t a -> m
foldMapWithKey1Default :: forall (t :: * -> *) m a.
(TraversableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1Default Key t -> a -> m
f = Const m (t Any) -> m
forall {k} a (b :: k). Const a b -> a
getConst (Const m (t Any) -> m) -> (t a -> Const m (t Any)) -> t a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key t -> a -> Const m Any) -> t a -> Const m (t Any)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key t -> a -> f b) -> t a -> f (t b)
traverseWithKey1 (\Key t
k -> m -> Const m Any
forall {k} a (b :: k). a -> Const a b
Const (m -> Const m Any) -> (a -> m) -> a -> Const m Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key t -> a -> m
f Key t
k)
{-# INLINE foldMapWithKey1Default #-}
type instance Key Identity = ()
instance Indexable Identity where
index :: forall a. Identity a -> Key Identity -> a
index (Identity a
a) Key Identity
_ = a
a
instance Lookup Identity where
lookup :: forall a. Key Identity -> Identity a -> Maybe a
lookup Key Identity
_ (Identity a
a) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
instance Adjustable Identity where
adjust :: forall a. (a -> a) -> Key Identity -> Identity a -> Identity a
adjust a -> a
f Key Identity
_ (Identity a
a) = a -> Identity a
forall a. a -> Identity a
Identity (a -> a
f a
a)
replace :: forall a. Key Identity -> a -> Identity a -> Identity a
replace Key Identity
_ a
b Identity a
_ = a -> Identity a
forall a. a -> Identity a
Identity a
b
instance Zip Identity where
zipWith :: forall a b c.
(a -> b -> c) -> Identity a -> Identity b -> Identity c
zipWith a -> b -> c
f (Identity a
a) (Identity b
b) = c -> Identity c
forall a. a -> Identity a
Identity (a -> b -> c
f a
a b
b)
instance ZipWithKey Identity where
zipWithKey :: forall a b c.
(Key Identity -> a -> b -> c)
-> Identity a -> Identity b -> Identity c
zipWithKey Key Identity -> a -> b -> c
f (Identity a
a) (Identity b
b) = c -> Identity c
forall a. a -> Identity a
Identity (Key Identity -> a -> b -> c
f () a
a b
b)
instance Keyed Identity where
mapWithKey :: forall a b. (Key Identity -> a -> b) -> Identity a -> Identity b
mapWithKey Key Identity -> a -> b
f = b -> Identity b
forall a. a -> Identity a
Identity (b -> Identity b) -> (Identity a -> b) -> Identity a -> Identity b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key Identity -> a -> b
f () (a -> b) -> (Identity a -> a) -> Identity a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity
instance FoldableWithKey Identity where
foldrWithKey :: forall a b. (Key Identity -> a -> b -> b) -> b -> Identity a -> b
foldrWithKey Key Identity -> a -> b -> b
f b
z (Identity a
a) = Key Identity -> a -> b -> b
f () a
a b
z
instance FoldableWithKey1 Identity where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key Identity -> a -> m) -> Identity a -> m
foldMapWithKey1 Key Identity -> a -> m
f (Identity a
a) = Key Identity -> a -> m
f () a
a
instance TraversableWithKey Identity where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key Identity -> a -> f b) -> Identity a -> f (Identity b)
traverseWithKey Key Identity -> a -> f b
f (Identity a
a) = b -> Identity b
forall a. a -> Identity a
Identity (b -> Identity b) -> f b -> f (Identity b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Identity -> a -> f b
f () a
a
instance TraversableWithKey1 Identity where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key Identity -> a -> f b) -> Identity a -> f (Identity b)
traverseWithKey1 Key Identity -> a -> f b
f (Identity a
a) = b -> Identity b
forall a. a -> Identity a
Identity (b -> Identity b) -> f b -> f (Identity b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key Identity -> a -> f b
f () a
a
type instance Key (IdentityT m) = Key m
instance Indexable m => Indexable (IdentityT m) where
index :: forall a. IdentityT m a -> Key (IdentityT m) -> a
index (IdentityT m a
m) Key (IdentityT m)
i = m a -> Key m -> a
forall a. m a -> Key m -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index m a
m Key m
Key (IdentityT m)
i
instance Lookup m => Lookup (IdentityT m) where
lookup :: forall a. Key (IdentityT m) -> IdentityT m a -> Maybe a
lookup Key (IdentityT m)
i (IdentityT m a
m) = Key m -> m a -> Maybe a
forall a. Key m -> m a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key m
Key (IdentityT m)
i m a
m
instance Zip m => Zip (IdentityT m) where
zipWith :: forall a b c.
(a -> b -> c) -> IdentityT m a -> IdentityT m b -> IdentityT m c
zipWith a -> b -> c
f (IdentityT m a
m) (IdentityT m b
n) = m c -> IdentityT m c
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT ((a -> b -> c) -> m a -> m b -> m c
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f m a
m m b
n)
instance ZipWithKey m => ZipWithKey (IdentityT m) where
zipWithKey :: forall a b c.
(Key (IdentityT m) -> a -> b -> c)
-> IdentityT m a -> IdentityT m b -> IdentityT m c
zipWithKey Key (IdentityT m) -> a -> b -> c
f (IdentityT m a
m) (IdentityT m b
n) = m c -> IdentityT m c
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT ((Key m -> a -> b -> c) -> m a -> m b -> m c
forall a b c. (Key m -> a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey Key m -> a -> b -> c
Key (IdentityT m) -> a -> b -> c
f m a
m m b
n)
instance Keyed m => Keyed (IdentityT m) where
mapWithKey :: forall a b.
(Key (IdentityT m) -> a -> b) -> IdentityT m a -> IdentityT m b
mapWithKey Key (IdentityT m) -> a -> b
f = m b -> IdentityT m b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m b -> IdentityT m b)
-> (IdentityT m a -> m b) -> IdentityT m a -> IdentityT m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key m -> a -> b) -> m a -> m b
forall a b. (Key m -> a -> b) -> m a -> m b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey Key m -> a -> b
Key (IdentityT m) -> a -> b
f (m a -> m b) -> (IdentityT m a -> m a) -> IdentityT m a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
instance FoldableWithKey m => FoldableWithKey (IdentityT m) where
foldrWithKey :: forall a b.
(Key (IdentityT m) -> a -> b -> b) -> b -> IdentityT m a -> b
foldrWithKey Key (IdentityT m) -> a -> b -> b
f b
z (IdentityT m a
m) = (Key m -> a -> b -> b) -> b -> m a -> b
forall a b. (Key m -> a -> b -> b) -> b -> m a -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey Key m -> a -> b -> b
Key (IdentityT m) -> a -> b -> b
f b
z m a
m
instance FoldableWithKey1 m => FoldableWithKey1 (IdentityT m) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (IdentityT m) -> a -> m) -> IdentityT m a -> m
foldMapWithKey1 Key (IdentityT m) -> a -> m
f (IdentityT m a
m) = (Key m -> a -> m) -> m a -> m
forall m a. Semigroup m => (Key m -> a -> m) -> m a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 Key m -> a -> m
Key (IdentityT m) -> a -> m
f m a
m
instance TraversableWithKey m => TraversableWithKey (IdentityT m) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (IdentityT m) -> a -> f b)
-> IdentityT m a -> f (IdentityT m b)
traverseWithKey Key (IdentityT m) -> a -> f b
f (IdentityT m a
a) = m b -> IdentityT m b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m b -> IdentityT m b) -> f (m b) -> f (IdentityT m b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key m -> a -> f b) -> m a -> f (m b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key m -> a -> f b) -> m a -> f (m b)
traverseWithKey Key m -> a -> f b
Key (IdentityT m) -> a -> f b
f m a
a
instance TraversableWithKey1 m => TraversableWithKey1 (IdentityT m) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (IdentityT m) -> a -> f b)
-> IdentityT m a -> f (IdentityT m b)
traverseWithKey1 Key (IdentityT m) -> a -> f b
f (IdentityT m a
a) = m b -> IdentityT m b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m b -> IdentityT m b) -> f (m b) -> f (IdentityT m b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key m -> a -> f b) -> m a -> f (m b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key m -> a -> f b) -> m a -> f (m b)
traverseWithKey1 Key m -> a -> f b
Key (IdentityT m) -> a -> f b
f m a
a
type instance Key ((->)a) = a
instance Keyed ((->)a) where
mapWithKey :: forall a b. (Key ((->) a) -> a -> b) -> (a -> a) -> a -> b
mapWithKey = (a -> a -> b) -> (a -> a) -> a -> b
(Key ((->) a) -> a -> b) -> (a -> a) -> a -> b
forall a b. (a -> a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>)
instance Zip ((->)a) where
zipWith :: forall a b c. (a -> b -> c) -> (a -> a) -> (a -> b) -> a -> c
zipWith a -> b -> c
f a -> a
g a -> b
h a
a = a -> b -> c
f (a -> a
g a
a) (a -> b
h a
a)
instance ZipWithKey ((->)a) where
zipWithKey :: forall a b c.
(Key ((->) a) -> a -> b -> c) -> (a -> a) -> (a -> b) -> a -> c
zipWithKey Key ((->) a) -> a -> b -> c
f a -> a
g a -> b
h a
a = Key ((->) a) -> a -> b -> c
f a
Key ((->) a)
a (a -> a
g a
a) (a -> b
h a
a)
instance Indexable ((->)a) where
index :: forall a. (a -> a) -> Key ((->) a) -> a
index = (a -> a) -> a -> a
(a -> a) -> Key ((->) a) -> a
forall a. a -> a
id
instance Lookup ((->)a) where
lookup :: forall a. Key ((->) a) -> (a -> a) -> Maybe a
lookup Key ((->) a)
i a -> a
f = a -> Maybe a
forall a. a -> Maybe a
Just (a -> a
f a
Key ((->) a)
i)
type instance Key (ReaderT e m) = (e, Key m)
instance Zip m => Zip (ReaderT e m) where
zipWith :: forall a b c.
(a -> b -> c) -> ReaderT e m a -> ReaderT e m b -> ReaderT e m c
zipWith a -> b -> c
f (ReaderT e -> m a
m) (ReaderT e -> m b
n) = (e -> m c) -> ReaderT e m c
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m c) -> ReaderT e m c) -> (e -> m c) -> ReaderT e m c
forall a b. (a -> b) -> a -> b
$ \e
a ->
(a -> b -> c) -> m a -> m b -> m c
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f (e -> m a
m e
a) (e -> m b
n e
a)
instance ZipWithKey m => ZipWithKey (ReaderT e m) where
zipWithKey :: forall a b c.
(Key (ReaderT e m) -> a -> b -> c)
-> ReaderT e m a -> ReaderT e m b -> ReaderT e m c
zipWithKey Key (ReaderT e m) -> a -> b -> c
f (ReaderT e -> m a
m) (ReaderT e -> m b
n) = (e -> m c) -> ReaderT e m c
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m c) -> ReaderT e m c) -> (e -> m c) -> ReaderT e m c
forall a b. (a -> b) -> a -> b
$ \e
a ->
(Key m -> a -> b -> c) -> m a -> m b -> m c
forall a b c. (Key m -> a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((e, Key m) -> a -> b -> c
Key (ReaderT e m) -> a -> b -> c
f ((e, Key m) -> a -> b -> c)
-> (Key m -> (e, Key m)) -> Key m -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) e
a) (e -> m a
m e
a) (e -> m b
n e
a)
instance Keyed m => Keyed (ReaderT e m) where
mapWithKey :: forall a b.
(Key (ReaderT e m) -> a -> b) -> ReaderT e m a -> ReaderT e m b
mapWithKey Key (ReaderT e m) -> a -> b
f (ReaderT e -> m a
m) = (e -> m b) -> ReaderT e m b
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m b) -> ReaderT e m b) -> (e -> m b) -> ReaderT e m b
forall a b. (a -> b) -> a -> b
$ \e
k -> (Key m -> a -> b) -> m a -> m b
forall a b. (Key m -> a -> b) -> m a -> m b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((e, Key m) -> a -> b
Key (ReaderT e m) -> a -> b
f ((e, Key m) -> a -> b) -> (Key m -> (e, Key m)) -> Key m -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) e
k) (e -> m a
m e
k)
instance Indexable m => Indexable (ReaderT e m) where
index :: forall a. ReaderT e m a -> Key (ReaderT e m) -> a
index (ReaderT e -> m a
f) (e
e,Key m
k) = m a -> Key m -> a
forall a. m a -> Key m -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index (e -> m a
f e
e) Key m
k
instance Lookup m => Lookup (ReaderT e m) where
lookup :: forall a. Key (ReaderT e m) -> ReaderT e m a -> Maybe a
lookup (e
e,Key m
k) (ReaderT e -> m a
f) = Key m -> m a -> Maybe a
forall a. Key m -> m a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key m
k (e -> m a
f e
e)
type instance Key (TracedT s w) = (s, Key w)
instance Zip w => Zip (TracedT s w) where
zipWith :: forall a b c.
(a -> b -> c) -> TracedT s w a -> TracedT s w b -> TracedT s w c
zipWith a -> b -> c
f (TracedT w (s -> a)
u) (TracedT w (s -> b)
v) = w (s -> c) -> TracedT s w c
forall m (w :: * -> *) a. w (m -> a) -> TracedT m w a
TracedT (w (s -> c) -> TracedT s w c) -> w (s -> c) -> TracedT s w c
forall a b. (a -> b) -> a -> b
$
((s -> a) -> (s -> b) -> s -> c)
-> w (s -> a) -> w (s -> b) -> w (s -> c)
forall a b c. (a -> b -> c) -> w a -> w b -> w c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith (\s -> a
a s -> b
b s
s -> a -> b -> c
f (s -> a
a s
s) (s -> b
b s
s)) w (s -> a)
u w (s -> b)
v
instance ZipWithKey w => ZipWithKey (TracedT s w) where
zipWithKey :: forall a b c.
(Key (TracedT s w) -> a -> b -> c)
-> TracedT s w a -> TracedT s w b -> TracedT s w c
zipWithKey Key (TracedT s w) -> a -> b -> c
f (TracedT w (s -> a)
u) (TracedT w (s -> b)
v) = w (s -> c) -> TracedT s w c
forall m (w :: * -> *) a. w (m -> a) -> TracedT m w a
TracedT (w (s -> c) -> TracedT s w c) -> w (s -> c) -> TracedT s w c
forall a b. (a -> b) -> a -> b
$
(Key w -> (s -> a) -> (s -> b) -> s -> c)
-> w (s -> a) -> w (s -> b) -> w (s -> c)
forall a b c. (Key w -> a -> b -> c) -> w a -> w b -> w c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (\Key w
k s -> a
a s -> b
b s
s -> Key (TracedT s w) -> a -> b -> c
f (s
s, Key w
k) (s -> a
a s
s) (s -> b
b s
s)) w (s -> a)
u w (s -> b)
v
instance Keyed w => Keyed (TracedT s w) where
mapWithKey :: forall a b.
(Key (TracedT s w) -> a -> b) -> TracedT s w a -> TracedT s w b
mapWithKey Key (TracedT s w) -> a -> b
f = w (s -> b) -> TracedT s w b
forall m (w :: * -> *) a. w (m -> a) -> TracedT m w a
TracedT (w (s -> b) -> TracedT s w b)
-> (TracedT s w a -> w (s -> b)) -> TracedT s w a -> TracedT s w b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key w -> (s -> a) -> s -> b) -> w (s -> a) -> w (s -> b)
forall a b. (Key w -> a -> b) -> w a -> w b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (\Key w
k' s -> a
g s
k -> Key (TracedT s w) -> a -> b
f (s
k, Key w
k') (s -> a
g s
k)) (w (s -> a) -> w (s -> b))
-> (TracedT s w a -> w (s -> a)) -> TracedT s w a -> w (s -> b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TracedT s w a -> w (s -> a)
forall m (w :: * -> *) a. TracedT m w a -> w (m -> a)
runTracedT
instance Indexable w => Indexable (TracedT s w) where
index :: forall a. TracedT s w a -> Key (TracedT s w) -> a
index (TracedT w (s -> a)
w) (s
e,Key w
k) = w (s -> a) -> Key w -> s -> a
forall a. w a -> Key w -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index w (s -> a)
w Key w
k s
e
instance Lookup w => Lookup (TracedT s w) where
lookup :: forall a. Key (TracedT s w) -> TracedT s w a -> Maybe a
lookup (s
e,Key w
k) (TracedT w (s -> a)
w) = ((s -> a) -> s -> a
forall a b. (a -> b) -> a -> b
$ s
e) ((s -> a) -> a) -> Maybe (s -> a) -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key w -> w (s -> a) -> Maybe (s -> a)
forall a. Key w -> w a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key w
k w (s -> a)
w
type instance Key IntMap = Int
instance Zip IntMap where
zipWith :: forall a b c. (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
zipWith = (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c. (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
IntMap.intersectionWith
instance ZipWithKey IntMap where
zipWithKey :: forall a b c.
(Key IntMap -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
zipWithKey = (Int -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
(Key IntMap -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c.
(Int -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
IntMap.intersectionWithKey
instance Keyed IntMap where
mapWithKey :: forall a b. (Key IntMap -> a -> b) -> IntMap a -> IntMap b
mapWithKey = (Int -> a -> b) -> IntMap a -> IntMap b
(Key IntMap -> a -> b) -> IntMap a -> IntMap b
forall a b. (Int -> a -> b) -> IntMap a -> IntMap b
IntMap.mapWithKey
instance FoldableWithKey IntMap where
#if MIN_VERSION_containers(0,5,0)
foldrWithKey :: forall a b. (Key IntMap -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey = (Int -> a -> b -> b) -> b -> IntMap a -> b
(Key IntMap -> a -> b -> b) -> b -> IntMap a -> b
forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
IntMap.foldrWithKey
#else
foldrWithKey = IntMap.foldWithKey
#endif
instance TraversableWithKey IntMap where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key IntMap -> a -> f b) -> IntMap a -> f (IntMap b)
traverseWithKey Key IntMap -> a -> f b
f = ([(Int, b)] -> IntMap b) -> f [(Int, b)] -> f (IntMap b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(Int, b)] -> IntMap b
forall a. [(Int, a)] -> IntMap a
IntMap.fromDistinctAscList (f [(Int, b)] -> f (IntMap b))
-> (IntMap a -> f [(Int, b)]) -> IntMap a -> f (IntMap b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, a) -> f (Int, b)) -> [(Int, a)] -> f [(Int, b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\(Int
k, a
v) -> (,) Int
k (b -> (Int, b)) -> f b -> f (Int, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key IntMap -> a -> f b
f Int
Key IntMap
k a
v) ([(Int, a)] -> f [(Int, b)])
-> (IntMap a -> [(Int, a)]) -> IntMap a -> f [(Int, b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
IntMap.toAscList
instance Indexable IntMap where
index :: forall a. IntMap a -> Key IntMap -> a
index = IntMap a -> Int -> a
IntMap a -> Key IntMap -> a
forall a. IntMap a -> Int -> a
(IntMap.!)
instance Lookup IntMap where
lookup :: forall a. Key IntMap -> IntMap a -> Maybe a
lookup = Int -> IntMap a -> Maybe a
Key IntMap -> IntMap a -> Maybe a
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup
instance Adjustable IntMap where
adjust :: forall a. (a -> a) -> Key IntMap -> IntMap a -> IntMap a
adjust = (a -> a) -> Int -> IntMap a -> IntMap a
(a -> a) -> Key IntMap -> IntMap a -> IntMap a
forall a. (a -> a) -> Int -> IntMap a -> IntMap a
IntMap.adjust
type instance Key (Compose f g) = (Key f, Key g)
instance (Zip f, Zip g) => Zip (Compose f g) where
zipWith :: forall a b c.
(a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c
zipWith a -> b -> c
f (Compose f (g a)
a) (Compose f (g b)
b) = f (g c) -> Compose f g c
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g c) -> Compose f g c) -> f (g c) -> Compose f g c
forall a b. (a -> b) -> a -> b
$ (g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g c)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith ((a -> b -> c) -> g a -> g b -> g c
forall a b c. (a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f) f (g a)
a f (g b)
b
instance (ZipWithKey f, ZipWithKey g) => ZipWithKey (Compose f g) where
zipWithKey :: forall a b c.
(Key (Compose f g) -> a -> b -> c)
-> Compose f g a -> Compose f g b -> Compose f g c
zipWithKey Key (Compose f g) -> a -> b -> c
f (Compose f (g a)
a) (Compose f (g b)
b) = f (g c) -> Compose f g c
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g c) -> Compose f g c) -> f (g c) -> Compose f g c
forall a b. (a -> b) -> a -> b
$
(Key f -> g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g c)
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((Key g -> a -> b -> c) -> g a -> g b -> g c
forall a b c. (Key g -> a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey ((Key g -> a -> b -> c) -> g a -> g b -> g c)
-> (Key f -> Key g -> a -> b -> c) -> Key f -> g a -> g b -> g c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key f, Key g) -> a -> b -> c)
-> (Key g -> (Key f, Key g)) -> Key g -> a -> b -> c
forall a b. (a -> b) -> (Key g -> a) -> Key g -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key f, Key g) -> a -> b -> c
Key (Compose f g) -> a -> b -> c
f ((Key g -> (Key f, Key g)) -> Key g -> a -> b -> c)
-> (Key f -> Key g -> (Key f, Key g))
-> Key f
-> Key g
-> a
-> b
-> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,)) f (g a)
a f (g b)
b
instance (Keyed f, Keyed g) => Keyed (Compose f g) where
mapWithKey :: forall a b.
(Key (Compose f g) -> a -> b) -> Compose f g a -> Compose f g b
mapWithKey Key (Compose f g) -> a -> b
f = f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g b) -> Compose f g b)
-> (Compose f g a -> f (g b)) -> Compose f g a -> Compose f g b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key f -> g a -> g b) -> f (g a) -> f (g b)
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (\Key f
k -> (Key g -> a -> b) -> g a -> g b
forall a b. (Key g -> a -> b) -> g a -> g b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey ((Key f, Key g) -> a -> b
Key (Compose f g) -> a -> b
f ((Key f, Key g) -> a -> b)
-> (Key g -> (Key f, Key g)) -> Key g -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) Key f
k)) (f (g a) -> f (g b))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (Indexable f, Indexable g) => Indexable (Compose f g) where
index :: forall a. Compose f g a -> Key (Compose f g) -> a
index (Compose f (g a)
fg) (Key f
i,Key g
j) = g a -> Key g -> a
forall a. g a -> Key g -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index (f (g a) -> Key f -> g a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f (g a)
fg Key f
i) Key g
j
instance (Lookup f, Lookup g) => Lookup (Compose f g) where
lookup :: forall a. Key (Compose f g) -> Compose f g a -> Maybe a
lookup (Key f
i,Key g
j) (Compose f (g a)
fg) = Key f -> f (g a) -> Maybe (g a)
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
i f (g a)
fg Maybe (g a) -> (g a -> Maybe a) -> Maybe a
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Key g -> g a -> Maybe a
forall a. Key g -> g a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key g
j
instance (FoldableWithKey f, FoldableWithKey m) => FoldableWithKey (Compose f m) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (Compose f m) -> a -> m) -> Compose f m a -> m
foldMapWithKey Key (Compose f m) -> a -> m
f = (Key f -> m a -> m) -> f (m a) -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (\Key f
k -> (Key m -> a -> m) -> m a -> m
forall m a. Monoid m => (Key m -> a -> m) -> m a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey ((Key f, Key m) -> a -> m
Key (Compose f m) -> a -> m
f ((Key f, Key m) -> a -> m)
-> (Key m -> (Key f, Key m)) -> Key m -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) Key f
k)) (f (m a) -> m) -> (Compose f m a -> f (m a)) -> Compose f m a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f m a -> f (m a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (FoldableWithKey1 f, FoldableWithKey1 m) => FoldableWithKey1 (Compose f m) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Compose f m) -> a -> m) -> Compose f m a -> m
foldMapWithKey1 Key (Compose f m) -> a -> m
f = (Key f -> m a -> m) -> f (m a) -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (\Key f
k -> (Key m -> a -> m) -> m a -> m
forall m a. Semigroup m => (Key m -> a -> m) -> m a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 ((Key f, Key m) -> a -> m
Key (Compose f m) -> a -> m
f ((Key f, Key m) -> a -> m)
-> (Key m -> (Key f, Key m)) -> Key m -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) Key f
k)) (f (m a) -> m) -> (Compose f m a -> f (m a)) -> Compose f m a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f m a -> f (m a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (TraversableWithKey f, TraversableWithKey m) => TraversableWithKey (Compose f m) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Compose f m) -> a -> f b)
-> Compose f m a -> f (Compose f m b)
traverseWithKey Key (Compose f m) -> a -> f b
f = (f (m b) -> Compose f m b) -> f (f (m b)) -> f (Compose f m b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (m b) -> Compose f m b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (f (m b)) -> f (Compose f m b))
-> (Compose f m a -> f (f (m b)))
-> Compose f m a
-> f (Compose f m b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key f -> m a -> f (m b)) -> f (m a) -> f (f (m b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey (\Key f
k -> (Key m -> a -> f b) -> m a -> f (m b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key m -> a -> f b) -> m a -> f (m b)
traverseWithKey ((Key f, Key m) -> a -> f b
Key (Compose f m) -> a -> f b
f ((Key f, Key m) -> a -> f b)
-> (Key m -> (Key f, Key m)) -> Key m -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) Key f
k)) (f (m a) -> f (f (m b)))
-> (Compose f m a -> f (m a)) -> Compose f m a -> f (f (m b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f m a -> f (m a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (TraversableWithKey1 f, TraversableWithKey1 m) => TraversableWithKey1 (Compose f m) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Compose f m) -> a -> f b)
-> Compose f m a -> f (Compose f m b)
traverseWithKey1 Key (Compose f m) -> a -> f b
f = (f (m b) -> Compose f m b) -> f (f (m b)) -> f (Compose f m b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (m b) -> Compose f m b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (f (m b)) -> f (Compose f m b))
-> (Compose f m a -> f (f (m b)))
-> Compose f m a
-> f (Compose f m b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key f -> m a -> f (m b)) -> f (m a) -> f (f (m b))
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 (\Key f
k -> (Key m -> a -> f b) -> m a -> f (m b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key m -> a -> f b) -> m a -> f (m b)
traverseWithKey1 ((Key f, Key m) -> a -> f b
Key (Compose f m) -> a -> f b
f ((Key f, Key m) -> a -> f b)
-> (Key m -> (Key f, Key m)) -> Key m -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) Key f
k)) (f (m a) -> f (f (m b)))
-> (Compose f m a -> f (m a)) -> Compose f m a -> f (f (m b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f m a -> f (m a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
type instance Key [] = Int
instance Zip [] where
zip :: forall a b. [a] -> [b] -> [(a, b)]
zip = [a] -> [b] -> [(a, b)]
forall a b. [a] -> [b] -> [(a, b)]
List.zip
zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith = (a -> b -> c) -> [a] -> [b] -> [c]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
List.zipWith
instance ZipWithKey [] where
zipWithKey :: forall a b c. (Key [] -> a -> b -> c) -> [a] -> [b] -> [c]
zipWithKey Key [] -> a -> b -> c
f = Int -> [a] -> [b] -> [c]
go Int
0 where
go :: Int -> [a] -> [b] -> [c]
go Int
_ [] [b]
_ = []
go Int
_ [a]
_ [] = []
go Int
n (a
x:[a]
xs) (b
y:[b]
ys) = Int
n' Int -> [c] -> [c]
forall a b. a -> b -> b
`seq` Key [] -> a -> b -> c
f Int
Key []
n a
x b
y c -> [c] -> [c]
forall a. a -> [a] -> [a]
: Int -> [a] -> [b] -> [c]
go Int
n' [a]
xs [b]
ys
where n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
instance Keyed [] where
mapWithKey :: forall a b. (Key [] -> a -> b) -> [a] -> [b]
mapWithKey Key [] -> a -> b
f [a]
xs0 = [a] -> Int -> [b]
go [a]
xs0 Int
0 where
go :: [a] -> Int -> [b]
go [] Int
_ = []
go (a
x:[a]
xs) Int
n = Key [] -> a -> b
f Int
Key []
n a
x b -> [b] -> [b]
forall a. a -> [a] -> [a]
: ([a] -> Int -> [b]
go [a]
xs (Int -> [b]) -> Int -> [b]
forall a b. (a -> b) -> a -> b
$! (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
instance FoldableWithKey [] where
foldrWithKey :: forall a b. (Key [] -> a -> b -> b) -> b -> [a] -> b
foldrWithKey Key [] -> a -> b -> b
f b
z0 [a]
xs0 = b -> [a] -> Int -> b
go b
z0 [a]
xs0 Int
0 where
go :: b -> [a] -> Int -> b
go b
z [] Int
_ = b
z
go b
z (a
x:[a]
xs) Int
n = Key [] -> a -> b -> b
f Int
Key []
n a
x (b -> [a] -> Int -> b
go b
z [a]
xs (Int -> b) -> Int -> b
forall a b. (a -> b) -> a -> b
$! (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
instance TraversableWithKey [] where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key [] -> a -> f b) -> [a] -> f [b]
traverseWithKey Key [] -> a -> f b
f [a]
xs0 = [a] -> Int -> f [b]
go [a]
xs0 Int
0 where
go :: [a] -> Int -> f [b]
go [] Int
_ = [b] -> f [b]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
go (a
x:[a]
xs) Int
n = (:) (b -> [b] -> [b]) -> f b -> f ([b] -> [b])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key [] -> a -> f b
f Int
Key []
n a
x f ([b] -> [b]) -> f [b] -> f [b]
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([a] -> Int -> f [b]
go [a]
xs (Int -> f [b]) -> Int -> f [b]
forall a b. (a -> b) -> a -> b
$! (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
instance Indexable [] where
index :: forall a. [a] -> Key [] -> a
index = [a] -> Int -> a
[a] -> Key [] -> a
forall a. HasCallStack => [a] -> Int -> a
(!!)
instance Lookup [] where
lookup :: forall a. Key [] -> [a] -> Maybe a
lookup = ([a] -> Maybe a) -> ([a] -> [a]) -> [a] -> Maybe a
forall a b. (a -> b) -> ([a] -> a) -> [a] -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> Maybe a
forall a. [a] -> Maybe a
listToMaybe (([a] -> [a]) -> [a] -> Maybe a)
-> (Int -> [a] -> [a]) -> Int -> [a] -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop
instance Adjustable [] where
adjust :: forall a. (a -> a) -> Key [] -> [a] -> [a]
adjust a -> a
f Key []
0 (a
x:[a]
xs) = a -> a
f a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs
adjust a -> a
_ Key []
_ [] = []
adjust a -> a
f Key []
n (a
x:[a]
xs) = Int
n' Int -> [a] -> [a]
forall a b. a -> b -> b
`seq` a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a -> a) -> Key [] -> [a] -> [a]
forall a. (a -> a) -> Key [] -> [a] -> [a]
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Int
Key []
n' [a]
xs where n' :: Int
n' = Int
Key []
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
type instance Key ZipList = Int
instance Zip ZipList where
zip :: forall a b. ZipList a -> ZipList b -> ZipList (a, b)
zip (ZipList [a]
xs) (ZipList [b]
ys) = [(a, b)] -> ZipList (a, b)
forall a. [a] -> ZipList a
ZipList ([a] -> [b] -> [(a, b)]
forall a b. [a] -> [b] -> [(a, b)]
forall (f :: * -> *) a b. Zip f => f a -> f b -> f (a, b)
zip [a]
xs [b]
ys)
zipWith :: forall a b c. (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c
zipWith a -> b -> c
f (ZipList [a]
xs) (ZipList [b]
ys) = [c] -> ZipList c
forall a. [a] -> ZipList a
ZipList ((a -> b -> c) -> [a] -> [b] -> [c]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f [a]
xs [b]
ys)
instance ZipWithKey ZipList where
zipWithKey :: forall a b c.
(Key ZipList -> a -> b -> c) -> ZipList a -> ZipList b -> ZipList c
zipWithKey Key ZipList -> a -> b -> c
f (ZipList [a]
xs) (ZipList [b]
ys) = [c] -> ZipList c
forall a. [a] -> ZipList a
ZipList ((Key [] -> a -> b -> c) -> [a] -> [b] -> [c]
forall a b c. (Key [] -> a -> b -> c) -> [a] -> [b] -> [c]
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey Key [] -> a -> b -> c
Key ZipList -> a -> b -> c
f [a]
xs [b]
ys)
instance Keyed ZipList where
mapWithKey :: forall a b. (Key ZipList -> a -> b) -> ZipList a -> ZipList b
mapWithKey Key ZipList -> a -> b
f = [b] -> ZipList b
forall a. [a] -> ZipList a
ZipList ([b] -> ZipList b) -> (ZipList a -> [b]) -> ZipList a -> ZipList b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key [] -> a -> b) -> [a] -> [b]
forall a b. (Key [] -> a -> b) -> [a] -> [b]
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey Key [] -> a -> b
Key ZipList -> a -> b
f ([a] -> [b]) -> (ZipList a -> [a]) -> ZipList a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
instance FoldableWithKey ZipList where
foldrWithKey :: forall a b. (Key ZipList -> a -> b -> b) -> b -> ZipList a -> b
foldrWithKey Key ZipList -> a -> b -> b
f b
z = (Key [] -> a -> b -> b) -> b -> [a] -> b
forall a b. (Key [] -> a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey Key [] -> a -> b -> b
Key ZipList -> a -> b -> b
f b
z ([a] -> b) -> (ZipList a -> [a]) -> ZipList a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
instance TraversableWithKey ZipList where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key ZipList -> a -> f b) -> ZipList a -> f (ZipList b)
traverseWithKey Key ZipList -> a -> f b
f = ([b] -> ZipList b) -> f [b] -> f (ZipList b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [b] -> ZipList b
forall a. [a] -> ZipList a
ZipList (f [b] -> f (ZipList b))
-> (ZipList a -> f [b]) -> ZipList a -> f (ZipList b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key [] -> a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key [] -> a -> f b) -> [a] -> f [b]
traverseWithKey Key [] -> a -> f b
Key ZipList -> a -> f b
f ([a] -> f [b]) -> (ZipList a -> [a]) -> ZipList a -> f [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
instance Indexable ZipList where
index :: forall a. ZipList a -> Key ZipList -> a
index (ZipList [a]
xs) Key ZipList
i = [a] -> Key [] -> a
forall a. [a] -> Key [] -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index [a]
xs Key []
Key ZipList
i
instance Lookup ZipList where
lookup :: forall a. Key ZipList -> ZipList a -> Maybe a
lookup Key ZipList
i = Key [] -> [a] -> Maybe a
forall a. Key [] -> [a] -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key []
Key ZipList
i ([a] -> Maybe a) -> (ZipList a -> [a]) -> ZipList a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
instance Adjustable ZipList where
adjust :: forall a. (a -> a) -> Key ZipList -> ZipList a -> ZipList a
adjust a -> a
f Key ZipList
i = [a] -> ZipList a
forall a. [a] -> ZipList a
ZipList ([a] -> ZipList a) -> (ZipList a -> [a]) -> ZipList a -> ZipList a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a) -> Key [] -> [a] -> [a]
forall a. (a -> a) -> Key [] -> [a] -> [a]
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key []
Key ZipList
i ([a] -> [a]) -> (ZipList a -> [a]) -> ZipList a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
instance Zip NonEmpty where
zipWith :: forall a b c.
(a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
zipWith = (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
forall a b c.
(a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
NonEmpty.zipWith
instance ZipWithKey NonEmpty where
zipWithKey :: forall a b c.
(Key NonEmpty -> a -> b -> c)
-> NonEmpty a -> NonEmpty b -> NonEmpty c
zipWithKey Key NonEmpty -> a -> b -> c
f (a
a:|[a]
as) (b
b:|[b]
bs) = Key NonEmpty -> a -> b -> c
f Int
Key NonEmpty
0 a
a b
b c -> [c] -> NonEmpty c
forall a. a -> [a] -> NonEmpty a
:| (Key [] -> a -> b -> c) -> [a] -> [b] -> [c]
forall a b c. (Key [] -> a -> b -> c) -> [a] -> [b] -> [c]
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (Int -> a -> b -> c
Key NonEmpty -> a -> b -> c
f (Int -> a -> b -> c) -> (Int -> Int) -> Int -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) [a]
as [b]
bs
instance Keyed NonEmpty where
mapWithKey :: forall a b. (Key NonEmpty -> a -> b) -> NonEmpty a -> NonEmpty b
mapWithKey Key NonEmpty -> a -> b
f (a
a:|[a]
as) = Key NonEmpty -> a -> b
f Int
Key NonEmpty
0 a
a b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:| (Key [] -> a -> b) -> [a] -> [b]
forall a b. (Key [] -> a -> b) -> [a] -> [b]
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Int -> a -> b
Key NonEmpty -> a -> b
f (Int -> a -> b) -> (Int -> Int) -> Int -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) [a]
as
instance FoldableWithKey NonEmpty where
foldrWithKey :: forall a b. (Key NonEmpty -> a -> b -> b) -> b -> NonEmpty a -> b
foldrWithKey Key NonEmpty -> a -> b -> b
f b
z (a
x:|[a]
xs) = Key NonEmpty -> a -> b -> b
f Int
Key NonEmpty
0 a
x ((Key [] -> a -> b -> b) -> b -> [a] -> b
forall a b. (Key [] -> a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
FoldableWithKey t =>
(Key t -> a -> b -> b) -> b -> t a -> b
foldrWithKey (Int -> a -> b -> b
Key NonEmpty -> a -> b -> b
f (Int -> a -> b -> b) -> (Int -> Int) -> Int -> a -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) b
z [a]
xs)
instance TraversableWithKey NonEmpty where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverseWithKey Key NonEmpty -> a -> f b
f (a
x :| [a]
xs) = b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
(:|) (b -> [b] -> NonEmpty b) -> f b -> f ([b] -> NonEmpty b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key NonEmpty -> a -> f b
f Int
Key NonEmpty
0 a
x f ([b] -> NonEmpty b) -> f [b] -> f (NonEmpty b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Key [] -> a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key [] -> a -> f b) -> [a] -> f [b]
traverseWithKey (Int -> a -> f b
Key NonEmpty -> a -> f b
f (Int -> a -> f b) -> (Int -> Int) -> Int -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) [a]
xs
instance Indexable NonEmpty where
index :: forall a. NonEmpty a -> Key NonEmpty -> a
index (a
x:|[a]
_) Key NonEmpty
0 = a
x
index (a
_:|[a]
xs) Key NonEmpty
i = [a]
xs [a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
Key NonEmpty
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
instance Lookup NonEmpty where
lookup :: forall a. Key NonEmpty -> NonEmpty a -> Maybe a
lookup Key NonEmpty
0 (a
x:|[a]
_) = a -> Maybe a
forall a. a -> Maybe a
Just a
x
lookup Key NonEmpty
n (a
_:|[a]
xs) = Key [] -> [a] -> Maybe a
forall a. Key [] -> [a] -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup (Int
Key NonEmpty
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [a]
xs
instance Adjustable NonEmpty where
adjust :: forall a. (a -> a) -> Key NonEmpty -> NonEmpty a -> NonEmpty a
adjust a -> a
f Key NonEmpty
0 (a
x:|[a]
xs) = a -> a
f a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
xs
adjust a -> a
f Key NonEmpty
n (a
x:|[a]
xs) = a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| (a -> a) -> Key [] -> [a] -> [a]
forall a. (a -> a) -> Key [] -> [a] -> [a]
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f (Int
Key NonEmpty
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [a]
xs
instance FoldableWithKey1 NonEmpty where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key NonEmpty -> a -> m) -> NonEmpty a -> m
foldMapWithKey1 Key NonEmpty -> a -> m
f (a
x:|[]) = Key NonEmpty -> a -> m
f Int
Key NonEmpty
0 a
x
foldMapWithKey1 Key NonEmpty -> a -> m
f (a
x:|(a
y:[a]
ys)) = Key NonEmpty -> a -> m
f Int
Key NonEmpty
0 a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (Key NonEmpty -> a -> m) -> NonEmpty a -> m
forall m a.
Semigroup m =>
(Key NonEmpty -> a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Int -> a -> m
Key NonEmpty -> a -> m
f (Int -> a -> m) -> (Int -> Int) -> Int -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) (a
ya -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:|[a]
ys)
instance TraversableWithKey1 NonEmpty where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverseWithKey1 Key NonEmpty -> a -> f b
f (a
x:|[]) = (b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:|[]) (b -> NonEmpty b) -> f b -> f (NonEmpty b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key NonEmpty -> a -> f b
f Int
Key NonEmpty
0 a
x
traverseWithKey1 Key NonEmpty -> a -> f b
f (a
x:|(a
y:[a]
ys)) = (\b
w (b
z:|[b]
zs) -> b
w b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:| (b
zb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
zs)) (b -> NonEmpty b -> NonEmpty b)
-> f b -> f (NonEmpty b -> NonEmpty b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key NonEmpty -> a -> f b
f Int
Key NonEmpty
0 a
x f (NonEmpty b -> NonEmpty b) -> f (NonEmpty b) -> f (NonEmpty b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key NonEmpty -> a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverseWithKey1 (Int -> a -> f b
Key NonEmpty -> a -> f b
f (Int -> a -> f b) -> (Int -> Int) -> Int -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) (a
y a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
ys)
type instance Key Seq = Int
instance Indexable Seq where
index :: forall a. Seq a -> Key Seq -> a
index = Seq a -> Int -> a
Seq a -> Key Seq -> a
forall a. Seq a -> Int -> a
Seq.index
instance Lookup Seq where
lookup :: forall a. Key Seq -> Seq a -> Maybe a
lookup Key Seq
i Seq a
s =
#if MIN_VERSION_containers(0,5,8)
Int -> Seq a -> Maybe a
forall a. Int -> Seq a -> Maybe a
Seq.lookup Int
Key Seq
i Seq a
s
#else
case viewl (Seq.drop i s) of
EmptyL -> Nothing
a Seq.:< _ -> Just a
#endif
instance Zip Seq where
zip :: forall a b. Seq a -> Seq b -> Seq (a, b)
zip = Seq a -> Seq b -> Seq (a, b)
forall a b. Seq a -> Seq b -> Seq (a, b)
Seq.zip
zipWith :: forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
zipWith = (a -> b -> c) -> Seq a -> Seq b -> Seq c
forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
Seq.zipWith
instance ZipWithKey Seq where
zipWithKey :: forall a b c. (Key Seq -> a -> b -> c) -> Seq a -> Seq b -> Seq c
zipWithKey Key Seq -> a -> b -> c
f Seq a
a Seq b
b = ((b -> c) -> b -> c) -> Seq (b -> c) -> Seq b -> Seq c
forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
Seq.zipWith (b -> c) -> b -> c
forall a. a -> a
id ((Int -> a -> b -> c) -> Seq a -> Seq (b -> c)
forall a b. (Int -> a -> b) -> Seq a -> Seq b
Seq.mapWithIndex Int -> a -> b -> c
Key Seq -> a -> b -> c
f Seq a
a) Seq b
b
instance Adjustable Seq where
adjust :: forall a. (a -> a) -> Key Seq -> Seq a -> Seq a
adjust a -> a
f Key Seq
i Seq a
xs =
#if MIN_VERSION_containers(0,5,8)
(a -> a) -> Int -> Seq a -> Seq a
forall a. (a -> a) -> Int -> Seq a -> Seq a
Seq.adjust' a -> a
f Int
Key Seq
i Seq a
xs
#else
case i `lookup` xs of
Nothing -> xs
Just x -> let !x' = f x
in Seq.update i x' xs
#endif
instance Keyed Seq where
mapWithKey :: forall a b. (Key Seq -> a -> b) -> Seq a -> Seq b
mapWithKey = (Int -> a -> b) -> Seq a -> Seq b
(Key Seq -> a -> b) -> Seq a -> Seq b
forall a b. (Int -> a -> b) -> Seq a -> Seq b
Seq.mapWithIndex
instance FoldableWithKey Seq where
foldrWithKey :: forall a b. (Key Seq -> a -> b -> b) -> b -> Seq a -> b
foldrWithKey = (Int -> a -> b -> b) -> b -> Seq a -> b
(Key Seq -> a -> b -> b) -> b -> Seq a -> b
forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
Seq.foldrWithIndex
foldlWithKey :: forall b a. (b -> Key Seq -> a -> b) -> b -> Seq a -> b
foldlWithKey = (b -> Int -> a -> b) -> b -> Seq a -> b
(b -> Key Seq -> a -> b) -> b -> Seq a -> b
forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
Seq.foldlWithIndex
#if MIN_VERSION_containers(0,5,8)
foldMapWithKey :: forall m a. Monoid m => (Key Seq -> a -> m) -> Seq a -> m
foldMapWithKey = (Int -> a -> m) -> Seq a -> m
(Key Seq -> a -> m) -> Seq a -> m
forall m a. Monoid m => (Int -> a -> m) -> Seq a -> m
Seq.foldMapWithIndex
#endif
instance TraversableWithKey Seq where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key Seq -> a -> f b) -> Seq a -> f (Seq b)
traverseWithKey Key Seq -> a -> f b
f =
#if MIN_VERSION_containers(0,5,8)
(Int -> a -> f b) -> Seq a -> f (Seq b)
forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> Seq a -> f (Seq b)
Seq.traverseWithIndex Int -> a -> f b
Key Seq -> a -> f b
f
#else
fmap Seq.fromList . traverseWithKey f . toList
#endif
type instance Key (Map k) = k
instance Ord k => Zip (Map k) where
zipWith :: forall a b c. (a -> b -> c) -> Map k a -> Map k b -> Map k c
zipWith = (a -> b -> c) -> Map k a -> Map k b -> Map k c
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
Map.intersectionWith
instance Ord k => ZipWithKey (Map k) where
zipWithKey :: forall a b c.
(Key (Map k) -> a -> b -> c) -> Map k a -> Map k b -> Map k c
zipWithKey = (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
(Key (Map k) -> a -> b -> c) -> Map k a -> Map k b -> Map k c
forall k a b c.
Ord k =>
(k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
Map.intersectionWithKey
instance Keyed (Map k) where
mapWithKey :: forall a b. (Key (Map k) -> a -> b) -> Map k a -> Map k b
mapWithKey = (k -> a -> b) -> Map k a -> Map k b
(Key (Map k) -> a -> b) -> Map k a -> Map k b
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey
instance Ord k => Indexable (Map k) where
index :: forall a. Map k a -> Key (Map k) -> a
index = Map k a -> k -> a
Map k a -> Key (Map k) -> a
forall k a. Ord k => Map k a -> k -> a
(Map.!)
instance Ord k => Lookup (Map k) where
lookup :: forall a. Key (Map k) -> Map k a -> Maybe a
lookup = k -> Map k a -> Maybe a
Key (Map k) -> Map k a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup
instance FoldableWithKey (Map k) where
foldrWithKey :: forall a b. (Key (Map k) -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey = (k -> a -> b -> b) -> b -> Map k a -> b
(Key (Map k) -> a -> b -> b) -> b -> Map k a -> b
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey
instance TraversableWithKey (Map k) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Map k) -> a -> f b) -> Map k a -> f (Map k b)
traverseWithKey Key (Map k) -> a -> f b
f = ([(k, b)] -> Map k b) -> f [(k, b)] -> f (Map k b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(k, b)] -> Map k b
forall k a. [(k, a)] -> Map k a
Map.fromDistinctAscList (f [(k, b)] -> f (Map k b))
-> (Map k a -> f [(k, b)]) -> Map k a -> f (Map k b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((k, a) -> f (k, b)) -> [(k, a)] -> f [(k, b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\(k
k, a
v) -> (,) k
k (b -> (k, b)) -> f b -> f (k, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key (Map k) -> a -> f b
f k
Key (Map k)
k a
v) ([(k, a)] -> f [(k, b)])
-> (Map k a -> [(k, a)]) -> Map k a -> f [(k, b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
Map.toAscList
instance Ord k => Adjustable (Map k) where
adjust :: forall a. (a -> a) -> Key (Map k) -> Map k a -> Map k a
adjust = (a -> a) -> k -> Map k a -> Map k a
(a -> a) -> Key (Map k) -> Map k a -> Map k a
forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust
type instance Key (Array i) = i
instance Ix i => Keyed (Array i) where
mapWithKey :: forall a b. (Key (Array i) -> a -> b) -> Array i a -> Array i b
mapWithKey Key (Array i) -> a -> b
f Array i a
arr = (i, i) -> [b] -> Array i b
forall i e. Ix i => (i, i) -> [e] -> Array i e
Array.listArray (Array i a -> (i, i)
forall i e. Array i e -> (i, i)
Array.bounds Array i a
arr) ([b] -> Array i b) -> [b] -> Array i b
forall a b. (a -> b) -> a -> b
$ ((i, a) -> b) -> [(i, a)] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map ((i -> a -> b) -> (i, a) -> b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry i -> a -> b
Key (Array i) -> a -> b
f) ([(i, a)] -> [b]) -> [(i, a)] -> [b]
forall a b. (a -> b) -> a -> b
$ Array i a -> [(i, a)]
forall i e. Ix i => Array i e -> [(i, e)]
Array.assocs Array i a
arr
instance Ix i => Indexable (Array i) where
index :: forall a. Array i a -> Key (Array i) -> a
index = Array i a -> i -> a
Array i a -> Key (Array i) -> a
forall i e. Ix i => Array i e -> i -> e
(Array.!)
instance Ix i => Lookup (Array i) where
lookup :: forall a. Key (Array i) -> Array i a -> Maybe a
lookup Key (Array i)
i Array i a
arr
| (i, i) -> i -> Bool
forall a. Ix a => (a, a) -> a -> Bool
inRange (Array i a -> (i, i)
forall i e. Array i e -> (i, i)
Array.bounds Array i a
arr) i
Key (Array i)
i = a -> Maybe a
forall a. a -> Maybe a
Just (Array i a
arr Array i a -> i -> a
forall i e. Ix i => Array i e -> i -> e
Array.! i
Key (Array i)
i)
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
instance Ix i => FoldableWithKey (Array i) where
foldrWithKey :: forall a b. (Key (Array i) -> a -> b -> b) -> b -> Array i a -> b
foldrWithKey Key (Array i) -> a -> b -> b
f b
z = ((i, a) -> b -> b) -> b -> [(i, a)] -> b
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Prelude.foldr ((i -> a -> b -> b) -> (i, a) -> b -> b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry i -> a -> b -> b
Key (Array i) -> a -> b -> b
f) b
z ([(i, a)] -> b) -> (Array i a -> [(i, a)]) -> Array i a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array i a -> [(i, a)]
forall i e. Ix i => Array i e -> [(i, e)]
Array.assocs
instance Ix i => TraversableWithKey (Array i) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Array i) -> a -> f b) -> Array i a -> f (Array i b)
traverseWithKey Key (Array i) -> a -> f b
f Array i a
arr = (i, i) -> [b] -> Array i b
forall i e. Ix i => (i, i) -> [e] -> Array i e
Array.listArray (Array i a -> (i, i)
forall i e. Array i e -> (i, i)
Array.bounds Array i a
arr) ([b] -> Array i b) -> f [b] -> f (Array i b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((i, a) -> f b) -> [(i, a)] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((i -> a -> f b) -> (i, a) -> f b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry i -> a -> f b
Key (Array i) -> a -> f b
f) (Array i a -> [(i, a)]
forall i e. Ix i => Array i e -> [(i, e)]
Array.assocs Array i a
arr)
instance Ix i => Adjustable (Array i) where
adjust :: forall a. (a -> a) -> Key (Array i) -> Array i a -> Array i a
adjust a -> a
f Key (Array i)
i Array i a
arr = Array i a
arr Array i a -> [(i, a)] -> Array i a
forall i e. Ix i => Array i e -> [(i, e)] -> Array i e
Array.// [(i
Key (Array i)
i, a -> a
f (Array i a
arr Array i a -> i -> a
forall i e. Ix i => Array i e -> i -> e
Array.! i
Key (Array i)
i))]
replace :: forall a. Key (Array i) -> a -> Array i a -> Array i a
replace Key (Array i)
i a
b Array i a
arr = Array i a
arr Array i a -> [(i, a)] -> Array i a
forall i e. Ix i => Array i e -> [(i, e)] -> Array i e
Array.// [(i
Key (Array i)
i, a
b)]
type instance Key (Functor.Sum f g) = Either (Key f) (Key g)
instance (Keyed f, Keyed g) => Keyed (Functor.Sum f g) where
mapWithKey :: forall a b. (Key (Sum f g) -> a -> b) -> Sum f g a -> Sum f g b
mapWithKey Key (Sum f g) -> a -> b
f (Functor.InL f a
a) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Functor.InL ((Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (Sum f g) -> a -> b
f (Either (Key f) (Key g) -> a -> b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a)
mapWithKey Key (Sum f g) -> a -> b
f (Functor.InR g a
b) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Functor.InR ((Key g -> a -> b) -> g a -> g b
forall a b. (Key g -> a -> b) -> g a -> g b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (Sum f g) -> a -> b
f (Either (Key f) (Key g) -> a -> b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b)
instance (Indexable f, Indexable g) => Indexable (Functor.Sum f g) where
index :: forall a. Sum f g a -> Key (Sum f g) -> a
index (Functor.InL f a
a) (Left Key f
x) = f a -> Key f -> a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f a
a Key f
x
index (Functor.InL f a
_) (Right Key g
_) = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"InL indexed with a Right key"
index (Functor.InR g a
b) (Right Key g
y) = g a -> Key g -> a
forall a. g a -> Key g -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index g a
b Key g
y
index (Functor.InR g a
_) (Left Key f
_) = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"InR indexed with a Left key"
instance (Lookup f, Lookup g) => Lookup (Functor.Sum f g) where
lookup :: forall a. Key (Sum f g) -> Sum f g a -> Maybe a
lookup (Left Key f
x) (Functor.InL f a
a) = Key f -> f a -> Maybe a
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
x f a
a
lookup (Right Key g
y) (Functor.InR g a
b) = Key g -> g a -> Maybe a
forall a. Key g -> g a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key g
y g a
b
lookup Key (Sum f g)
_ Sum f g a
_ = Maybe a
forall a. Maybe a
Nothing
instance (Adjustable f, Adjustable g) => Adjustable (Functor.Sum f g) where
adjust :: forall a. (a -> a) -> Key (Sum f g) -> Sum f g a -> Sum f g a
adjust a -> a
f (Left Key f
x) (Functor.InL f a
a) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Functor.InL ((a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key f
x f a
a)
adjust a -> a
f (Right Key g
y) (Functor.InR g a
b) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Functor.InR ((a -> a) -> Key g -> g a -> g a
forall a. (a -> a) -> Key g -> g a -> g a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key g
y g a
b)
adjust a -> a
_ Key (Sum f g)
_ Sum f g a
x = Sum f g a
x
replace :: forall a. Key (Sum f g) -> a -> Sum f g a -> Sum f g a
replace (Left Key f
x) a
v (Functor.InL f a
a) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Functor.InL (Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
x a
v f a
a)
replace (Right Key g
y) a
v (Functor.InR g a
b) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Functor.InR (Key g -> a -> g a -> g a
forall a. Key g -> a -> g a -> g a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key g
y a
v g a
b)
replace Key (Sum f g)
_ a
_ Sum f g a
x = Sum f g a
x
instance (FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (Functor.Sum f g) where
foldMapWithKey :: forall m a. Monoid m => (Key (Sum f g) -> a -> m) -> Sum f g a -> m
foldMapWithKey Key (Sum f g) -> a -> m
f (Functor.InL f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (Sum f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a
foldMapWithKey Key (Sum f g) -> a -> m
f (Functor.InR g a
b) = (Key g -> a -> m) -> g a -> m
forall m a. Monoid m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (Sum f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Functor.Sum f g) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Sum f g) -> a -> m) -> Sum f g a -> m
foldMapWithKey1 Key (Sum f g) -> a -> m
f (Functor.InL f a
a) = (Key f -> a -> m) -> f a -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (Sum f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a
foldMapWithKey1 Key (Sum f g) -> a -> m
f (Functor.InR g a
b) = (Key g -> a -> m) -> g a -> m
forall m a. Semigroup m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (Sum f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (Functor.Sum f g) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Sum f g) -> a -> f b) -> Sum f g a -> f (Sum f g b)
traverseWithKey Key (Sum f g) -> a -> f b
f (Functor.InL f a
a) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Functor.InL (f b -> Sum f g b) -> f (f b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (Sum f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a
traverseWithKey Key (Sum f g) -> a -> f b
f (Functor.InR g a
b) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Functor.InR (g b -> Sum f g b) -> f (g b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (Sum f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (Functor.Sum f g) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Sum f g) -> a -> f b) -> Sum f g a -> f (Sum f g b)
traverseWithKey1 Key (Sum f g) -> a -> f b
f (Functor.InL f a
a) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Functor.InL (f b -> Sum f g b) -> f (f b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (Sum f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a
traverseWithKey1 Key (Sum f g) -> a -> f b
f (Functor.InR g a
b) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Functor.InR (g b -> Sum f g b) -> f (g b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (Sum f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
type instance Key (Product f g) = Either (Key f) (Key g)
instance (Keyed f, Keyed g) => Keyed (Product f g) where
mapWithKey :: forall a b.
(Key (Product f g) -> a -> b) -> Product f g a -> Product f g b
mapWithKey Key (Product f g) -> a -> b
f (Pair f a
a g a
b) = f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ((Key f -> a -> b) -> f a -> f b
forall a b. (Key f -> a -> b) -> f a -> f b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (Product f g) -> a -> b
f (Either (Key f) (Key g) -> a -> b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a) ((Key g -> a -> b) -> g a -> g b
forall a b. (Key g -> a -> b) -> g a -> g b
forall (f :: * -> *) a b.
Keyed f =>
(Key f -> a -> b) -> f a -> f b
mapWithKey (Either (Key f) (Key g) -> a -> b
Key (Product f g) -> a -> b
f (Either (Key f) (Key g) -> a -> b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b)
instance (Indexable f, Indexable g) => Indexable (Product f g) where
index :: forall a. Product f g a -> Key (Product f g) -> a
index (Pair f a
a g a
_) (Left Key f
i) = f a -> Key f -> a
forall a. f a -> Key f -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index f a
a Key f
i
index (Pair f a
_ g a
b) (Right Key g
j) = g a -> Key g -> a
forall a. g a -> Key g -> a
forall (f :: * -> *) a. Indexable f => f a -> Key f -> a
index g a
b Key g
j
instance (Lookup f, Lookup g) => Lookup (Product f g) where
lookup :: forall a. Key (Product f g) -> Product f g a -> Maybe a
lookup (Left Key f
i) (Pair f a
a g a
_) = Key f -> f a -> Maybe a
forall a. Key f -> f a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key f
i f a
a
lookup (Right Key g
j) (Pair f a
_ g a
b) = Key g -> g a -> Maybe a
forall a. Key g -> g a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup Key g
j g a
b
instance (Zip f, Zip g) => Zip (Product f g) where
zipWith :: forall a b c.
(a -> b -> c) -> Product f g a -> Product f g b -> Product f g c
zipWith a -> b -> c
f (Pair f a
a g a
b) (Pair f b
c g b
d) = f c -> g c -> Product f g c
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ((a -> b -> c) -> f a -> f b -> f c
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f f a
a f b
c) ((a -> b -> c) -> g a -> g b -> g c
forall a b c. (a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith a -> b -> c
f g a
b g b
d)
instance (ZipWithKey f, ZipWithKey g) => ZipWithKey (Product f g) where
zipWithKey :: forall a b c.
(Key (Product f g) -> a -> b -> c)
-> Product f g a -> Product f g b -> Product f g c
zipWithKey Key (Product f g) -> a -> b -> c
f (Pair f a
a g a
b) (Pair f b
c g b
d) = f c -> g c -> Product f g c
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ((Key f -> a -> b -> c) -> f a -> f b -> f c
forall a b c. (Key f -> a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (Either (Key f) (Key g) -> a -> b -> c
Key (Product f g) -> a -> b -> c
f (Either (Key f) (Key g) -> a -> b -> c)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a f b
c) ((Key g -> a -> b -> c) -> g a -> g b -> g c
forall a b c. (Key g -> a -> b -> c) -> g a -> g b -> g c
forall (f :: * -> *) a b c.
ZipWithKey f =>
(Key f -> a -> b -> c) -> f a -> f b -> f c
zipWithKey (Either (Key f) (Key g) -> a -> b -> c
Key (Product f g) -> a -> b -> c
f (Either (Key f) (Key g) -> a -> b -> c)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b g b
d)
instance (FoldableWithKey f, FoldableWithKey g) => FoldableWithKey (Product f g) where
foldMapWithKey :: forall m a.
Monoid m =>
(Key (Product f g) -> a -> m) -> Product f g a -> m
foldMapWithKey Key (Product f g) -> a -> m
f (Pair f a
a g a
b) = (Key f -> a -> m) -> f a -> m
forall m a. Monoid m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (Product f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (Key g -> a -> m) -> g a -> m
forall m a. Monoid m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey t, Monoid m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey (Either (Key f) (Key g) -> a -> m
Key (Product f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (FoldableWithKey1 f, FoldableWithKey1 g) => FoldableWithKey1 (Product f g) where
foldMapWithKey1 :: forall m a.
Semigroup m =>
(Key (Product f g) -> a -> m) -> Product f g a -> m
foldMapWithKey1 Key (Product f g) -> a -> m
f (Pair f a
a g a
b) = (Key f -> a -> m) -> f a -> m
forall m a. Semigroup m => (Key f -> a -> m) -> f a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (Product f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (Key g -> a -> m) -> g a -> m
forall m a. Semigroup m => (Key g -> a -> m) -> g a -> m
forall (t :: * -> *) m a.
(FoldableWithKey1 t, Semigroup m) =>
(Key t -> a -> m) -> t a -> m
foldMapWithKey1 (Either (Key f) (Key g) -> a -> m
Key (Product f g) -> a -> m
f (Either (Key f) (Key g) -> a -> m)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (TraversableWithKey f, TraversableWithKey g) => TraversableWithKey (Product f g) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (Product f g) -> a -> f b)
-> Product f g a -> f (Product f g b)
traverseWithKey Key (Product f g) -> a -> f b
f (Pair f a
a g a
b) = f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair (f b -> g b -> Product f g b)
-> f (f b) -> f (g b -> Product f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (Product f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a f (g b -> Product f g b) -> f (g b) -> f (Product f g b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey t, Applicative f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey (Either (Key f) (Key g) -> a -> f b
Key (Product f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (TraversableWithKey1 f, TraversableWithKey1 g) => TraversableWithKey1 (Product f g) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key (Product f g) -> a -> f b)
-> Product f g a -> f (Product f g b)
traverseWithKey1 Key (Product f g) -> a -> f b
f (Pair f a
a g a
b) = f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair (f b -> g b -> Product f g b)
-> f (f b) -> f (g b -> Product f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key f -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key f -> a -> f b) -> f a -> f (f b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (Product f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key f -> Either (Key f) (Key g)) -> Key f -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key f -> Either (Key f) (Key g)
forall a b. a -> Either a b
Left) f a
a f (g b -> Product f g b) -> f (g b) -> f (Product f g b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (Key g -> a -> f b) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(TraversableWithKey1 t, Apply f) =>
(Key t -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Apply f =>
(Key g -> a -> f b) -> g a -> f (g b)
traverseWithKey1 (Either (Key f) (Key g) -> a -> f b
Key (Product f g) -> a -> f b
f (Either (Key f) (Key g) -> a -> f b)
-> (Key g -> Either (Key f) (Key g)) -> Key g -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key g -> Either (Key f) (Key g)
forall a b. b -> Either a b
Right) g a
b
instance (Adjustable f, Adjustable g) => Adjustable (Product f g) where
adjust :: forall a.
(a -> a) -> Key (Product f g) -> Product f g a -> Product f g a
adjust a -> a
f (Left Key f
i) (Pair f a
a g a
b) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair ((a -> a) -> Key f -> f a -> f a
forall a. (a -> a) -> Key f -> f a -> f a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key f
i f a
a) g a
b
adjust a -> a
f (Right Key g
j) (Pair f a
a g a
b) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair f a
a ((a -> a) -> Key g -> g a -> g a
forall a. (a -> a) -> Key g -> g a -> g a
forall (f :: * -> *) a.
Adjustable f =>
(a -> a) -> Key f -> f a -> f a
adjust a -> a
f Key g
j g a
b)
replace :: forall a. Key (Product f g) -> a -> Product f g a -> Product f g a
replace (Left Key f
i) a
v (Pair f a
a g a
b) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair (Key f -> a -> f a -> f a
forall a. Key f -> a -> f a -> f a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key f
i a
v f a
a) g a
b
replace (Right Key g
j) a
v (Pair f a
a g a
b) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair f a
a (Key g -> a -> g a -> g a
forall a. Key g -> a -> g a -> g a
forall (f :: * -> *) a. Adjustable f => Key f -> a -> f a -> f a
replace Key g
j a
v g a
b)
type instance Key ((,) k) = k
instance Keyed ((,) k) where
mapWithKey :: forall a b. (Key ((,) k) -> a -> b) -> (k, a) -> (k, b)
mapWithKey Key ((,) k) -> a -> b
f (k
k, a
a) = (k
k, Key ((,) k) -> a -> b
f k
Key ((,) k)
k a
a)
instance FoldableWithKey ((,) k) where
foldMapWithKey :: forall m a. Monoid m => (Key ((,) k) -> a -> m) -> (k, a) -> m
foldMapWithKey = (k -> a -> m) -> (k, a) -> m
(Key ((,) k) -> a -> m) -> (k, a) -> m
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
instance FoldableWithKey1 ((,) k) where
foldMapWithKey1 :: forall m a. Semigroup m => (Key ((,) k) -> a -> m) -> (k, a) -> m
foldMapWithKey1 = (k -> a -> m) -> (k, a) -> m
(Key ((,) k) -> a -> m) -> (k, a) -> m
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
instance TraversableWithKey ((,) k) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key ((,) k) -> a -> f b) -> (k, a) -> f (k, b)
traverseWithKey Key ((,) k) -> a -> f b
f (k
k, a
a) = (,) k
k (b -> (k, b)) -> f b -> f (k, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key ((,) k) -> a -> f b
f k
Key ((,) k)
k a
a
instance TraversableWithKey1 ((,) k) where
traverseWithKey1 :: forall (f :: * -> *) a b.
Apply f =>
(Key ((,) k) -> a -> f b) -> (k, a) -> f (k, b)
traverseWithKey1 Key ((,) k) -> a -> f b
f (k
k, a
a) = (,) k
k (b -> (k, b)) -> f b -> f (k, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key ((,) k) -> a -> f b
f k
Key ((,) k)
k a
a
type instance Key (HashMap k) = k
instance Keyed (HashMap k) where
mapWithKey :: forall a b.
(Key (HashMap k) -> a -> b) -> HashMap k a -> HashMap k b
mapWithKey = (k -> a -> b) -> HashMap k a -> HashMap k b
(Key (HashMap k) -> a -> b) -> HashMap k a -> HashMap k b
forall k v1 v2. (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
HashMap.mapWithKey
instance (Eq k, Hashable k) => Indexable (HashMap k) where
index :: forall a. HashMap k a -> Key (HashMap k) -> a
index = HashMap k a -> k -> a
HashMap k a -> Key (HashMap k) -> a
forall k v.
(Eq k, Hashable k, HasCallStack) =>
HashMap k v -> k -> v
(HashMap.!)
instance (Eq k, Hashable k) => Lookup (HashMap k) where
lookup :: forall a. Key (HashMap k) -> HashMap k a -> Maybe a
lookup = k -> HashMap k a -> Maybe a
Key (HashMap k) -> HashMap k a -> Maybe a
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup
instance (Eq k, Hashable k) => Zip (HashMap k) where
zipWith :: forall a b c.
(a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c
zipWith = (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c
forall k v1 v2 v3.
(Eq k, Hashable k) =>
(v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
HashMap.intersectionWith
instance (Eq k, Hashable k) => ZipWithKey (HashMap k) where
zipWithKey :: forall a b c.
(Key (HashMap k) -> a -> b -> c)
-> HashMap k a -> HashMap k b -> HashMap k c
zipWithKey Key (HashMap k) -> a -> b -> c
f HashMap k a
a HashMap k b
b = (HashMap k c -> k -> a -> HashMap k c)
-> HashMap k c -> HashMap k a -> HashMap k c
forall a k v. (a -> k -> v -> a) -> a -> HashMap k v -> a
HashMap.foldlWithKey' HashMap k c -> k -> a -> HashMap k c
go HashMap k c
forall k v. HashMap k v
HashMap.empty HashMap k a
a
where
go :: HashMap k c -> k -> a -> HashMap k c
go HashMap k c
m k
k a
v = case Key (HashMap k) -> HashMap k b -> Maybe b
forall a. Key (HashMap k) -> HashMap k a -> Maybe a
forall (f :: * -> *) a. Lookup f => Key f -> f a -> Maybe a
lookup k
Key (HashMap k)
k HashMap k b
b of
Just b
w -> k -> c -> HashMap k c -> HashMap k c
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert k
k (Key (HashMap k) -> a -> b -> c
f k
Key (HashMap k)
k a
v b
w) HashMap k c
m
Maybe b
_ -> HashMap k c
m
instance FoldableWithKey (HashMap k) where
foldrWithKey :: forall a b.
(Key (HashMap k) -> a -> b -> b) -> b -> HashMap k a -> b
foldrWithKey = (k -> a -> b -> b) -> b -> HashMap k a -> b
(Key (HashMap k) -> a -> b -> b) -> b -> HashMap k a -> b
forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
HashMap.foldrWithKey
instance TraversableWithKey (HashMap k) where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key (HashMap k) -> a -> f b) -> HashMap k a -> f (HashMap k b)
traverseWithKey = (k -> a -> f b) -> HashMap k a -> f (HashMap k b)
(Key (HashMap k) -> a -> f b) -> HashMap k a -> f (HashMap k b)
forall (f :: * -> *) k v1 v2.
Applicative f =>
(k -> v1 -> f v2) -> HashMap k v1 -> f (HashMap k v2)
HashMap.traverseWithKey
type instance Key Maybe = ()
instance Keyed Maybe where
mapWithKey :: forall a b. (Key Maybe -> a -> b) -> Maybe a -> Maybe b
mapWithKey Key Maybe -> a -> b
f = (a -> b) -> Maybe a -> Maybe b
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key Maybe -> a -> b
f ())
instance Indexable Maybe where
index :: forall a. Maybe a -> Key Maybe -> a
index = a -> () -> a
forall a b. a -> b -> a
const (a -> () -> a) -> (Maybe a -> a) -> Maybe a -> () -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe a -> a
forall a. HasCallStack => Maybe a -> a
fromJust
instance Lookup Maybe where
lookup :: forall a. Key Maybe -> Maybe a -> Maybe a
lookup Key Maybe
_ Maybe a
mb = Maybe a
mb
instance Zip Maybe where
zipWith :: forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
zipWith a -> b -> c
f (Just a
a) (Just b
b) = c -> Maybe c
forall a. a -> Maybe a
Just (a -> b -> c
f a
a b
b)
zipWith a -> b -> c
_ Maybe a
_ Maybe b
_ = [Char] -> Maybe c
forall a. HasCallStack => [Char] -> a
error [Char]
"zipWith: Nothing"
instance ZipWithKey Maybe where
zipWithKey :: forall a b c.
(Key Maybe -> a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
zipWithKey Key Maybe -> a -> b -> c
f = (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
forall (f :: * -> *) a b c.
Zip f =>
(a -> b -> c) -> f a -> f b -> f c
zipWith (Key Maybe -> a -> b -> c
f ())
instance FoldableWithKey Maybe where
foldMapWithKey :: forall m a. Monoid m => (Key Maybe -> a -> m) -> Maybe a -> m
foldMapWithKey Key Maybe -> a -> m
f = (a -> m) -> Maybe a -> m
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Key Maybe -> a -> m
f ())
instance TraversableWithKey Maybe where
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Key Maybe -> a -> f b) -> Maybe a -> f (Maybe b)
traverseWithKey Key Maybe -> a -> f b
f = (a -> f b) -> Maybe a -> f (Maybe b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse (Key Maybe -> a -> f b
f ())