{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
#include "lens-common.h"
module Control.Lens.Each
  (
  
    Each(..)
  ) where
import Prelude ()
import Control.Lens.Traversal
import Control.Lens.Internal.ByteString
import Control.Lens.Internal.Prelude
import Data.Array.Unboxed as Unboxed
import Data.Array.IArray as IArray
import qualified Data.ByteString as StrictB
import qualified Data.ByteString.Lazy as LazyB
import Data.Complex
import Data.HashMap.Lazy (HashMap)
import Data.IntMap (IntMap)
import Data.Map (Map)
import Data.Sequence (Seq)
import Data.Text.Lens (text)
import qualified Data.Text as StrictT
import qualified Data.Text.Lazy as LazyT
import Data.Tree as Tree
import Data.Vector.Generic.Lens (vectorTraverse)
import qualified Data.Vector as Vector
import qualified Data.Vector.Primitive as Prim
import Data.Vector.Primitive (Prim)
import qualified Data.Vector.Storable as Storable
import Data.Vector.Storable (Storable)
import qualified Data.Vector.Unboxed as Unboxed
import Data.Vector.Unboxed (Unbox)
import Data.Word
import qualified Data.Strict as S
import Data.These (These (..))
class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
  each :: Traversal s t a b
  default each :: (Traversable g, s ~ g a, t ~ g b) => Traversal s t a b
  each = (a -> f b) -> s -> f t
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
  {-# INLINE each #-}
instance (a~a', b~b') => Each (a,a') (b,b') a b where
  each :: (a -> f b) -> (a, a') -> f (b, b')
each a -> f b
f ~(a
a,a'
b) = (,) (b -> b -> (b, b)) -> f b -> f (b -> (b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> (b, b)) -> f b -> f (b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a'
b
  {-# INLINE each #-}
instance (a~a2, a~a3, b~b2, b~b3) => Each (a,a2,a3) (b,b2,b3) a b where
  each :: (a -> f b) -> (a, a2, a3) -> f (b, b2, b3)
each a -> f b
f ~(a
a,a2
b,a3
c) = (,,) (b -> b -> b -> (b, b, b)) -> f b -> f (b -> b -> (b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> (b, b, b)) -> f b -> f (b -> (b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> (b, b, b)) -> f b -> f (b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c
  {-# INLINE each #-}
instance (a~a2, a~a3, a~a4, b~b2, b~b3, b~b4) => Each (a,a2,a3,a4) (b,b2,b3,b4) a b where
  each :: (a -> f b) -> (a, a2, a3, a4) -> f (b, b2, b3, b4)
each a -> f b
f ~(a
a,a2
b,a3
c,a4
d) = (,,,) (b -> b -> b -> b -> (b, b, b, b))
-> f b -> f (b -> b -> b -> (b, b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> b -> (b, b, b, b))
-> f b -> f (b -> b -> (b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> b -> (b, b, b, b)) -> f b -> f (b -> (b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c f (b -> (b, b, b, b)) -> f b -> f (b, b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a4
d
  {-# INLINE each #-}
instance (a~a2, a~a3, a~a4, a~a5, b~b2, b~b3, b~b4, b~b5) => Each (a,a2,a3,a4,a5) (b,b2,b3,b4,b5) a b where
  each :: (a -> f b) -> (a, a2, a3, a4, a5) -> f (b, b2, b3, b4, b5)
each a -> f b
f ~(a
a,a2
b,a3
c,a4
d,a5
e) = (,,,,) (b -> b -> b -> b -> b -> (b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> (b, b, b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> b -> b -> (b, b, b, b, b))
-> f b -> f (b -> b -> b -> (b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> b -> b -> (b, b, b, b, b))
-> f b -> f (b -> b -> (b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c f (b -> b -> (b, b, b, b, b)) -> f b -> f (b -> (b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a4
d f (b -> (b, b, b, b, b)) -> f b -> f (b, b, b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a5
e
  {-# INLINE each #-}
instance (a~a2, a~a3, a~a4, a~a5, a~a6, b~b2, b~b3, b~b4, b~b5, b~b6) => Each (a,a2,a3,a4,a5,a6) (b,b2,b3,b4,b5,b6) a b where
  each :: (a -> f b) -> (a, a2, a3, a4, a5, a6) -> f (b, b2, b3, b4, b5, b6)
each a -> f b
f ~(a
a,a2
b,a3
c,a4
d,a5
e,a6
g) = (,,,,,) (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> b -> (b, b, b, b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> b -> b -> b -> (b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> (b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> b -> b -> b -> (b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> (b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c f (b -> b -> b -> (b, b, b, b, b, b))
-> f b -> f (b -> b -> (b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a4
d f (b -> b -> (b, b, b, b, b, b))
-> f b -> f (b -> (b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a5
e f (b -> (b, b, b, b, b, b)) -> f b -> f (b, b, b, b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a6
g
  {-# INLINE each #-}
instance (a~a2, a~a3, a~a4, a~a5, a~a6, a~a7, b~b2, b~b3, b~b4, b~b5, b~b6, b~b7) => Each (a,a2,a3,a4,a5,a6,a7) (b,b2,b3,b4,b5,b6,b7) a b where
  each :: (a -> f b)
-> (a, a2, a3, a4, a5, a6, a7) -> f (b, b2, b3, b4, b5, b6, b7)
each a -> f b
f ~(a
a,a2
b,a3
c,a4
d,a5
e,a6
g,a7
h) = (,,,,,,) (b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> b -> (b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> b -> b -> b -> b -> (b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> (b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c f (b -> b -> b -> b -> (b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> (b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a4
d f (b -> b -> b -> (b, b, b, b, b, b, b))
-> f b -> f (b -> b -> (b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a5
e f (b -> b -> (b, b, b, b, b, b, b))
-> f b -> f (b -> (b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a6
g f (b -> (b, b, b, b, b, b, b)) -> f b -> f (b, b, b, b, b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a7
h
  {-# INLINE each #-}
instance (a~a2, a~a3, a~a4, a~a5, a~a6, a~a7, a~a8, b~b2, b~b3, b~b4, b~b5, b~b6, b~b7, b~b8) => Each (a,a2,a3,a4,a5,a6,a7,a8) (b,b2,b3,b4,b5,b6,b7,b8) a b where
  each :: (a -> f b)
-> (a, a2, a3, a4, a5, a6, a7, a8)
-> f (b, b2, b3, b4, b5, b6, b7, b8)
each a -> f b
f ~(a
a,a2
b,a3
c,a4
d,a5
e,a6
g,a7
h,a8
i) = (,,,,,,,) (b -> b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
-> f b
-> f (b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
-> f b
-> f (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c f (b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a4
d f (b -> b -> b -> b -> (b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a5
e f (b -> b -> b -> (b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a6
g f (b -> b -> (b, b, b, b, b, b, b, b))
-> f b -> f (b -> (b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a7
h f (b -> (b, b, b, b, b, b, b, b))
-> f b -> f (b, b, b, b, b, b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a8
i
  {-# INLINE each #-}
instance (a~a2, a~a3, a~a4, a~a5, a~a6, a~a7, a~a8, a~a9, b~b2, b~b3, b~b4, b~b5, b~b6, b~b7, b~b8, b~b9) => Each (a,a2,a3,a4,a5,a6,a7,a8,a9) (b,b2,b3,b4,b5,b6,b7,b8,b9) a b where
  each :: (a -> f b)
-> (a, a2, a3, a4, a5, a6, a7, a8, a9)
-> f (b, b2, b3, b4, b5, b6, b7, b8, b9)
each a -> f b
f ~(a
a,a2
b,a3
c,a4
d,a5
e,a6
g,a7
h,a8
i,a9
j) = (,,,,,,,,) (b
 -> b
 -> b
 -> b
 -> b
 -> b
 -> b
 -> b
 -> b
 -> (b, b, b, b, b, b, b, b, b))
-> f b
-> f (b
      -> b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b
   -> b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b
-> f (b
      -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a2
b f (b -> b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b
-> f (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a3
c f (b -> b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a4
d f (b -> b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a5
e f (b -> b -> b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a6
g f (b -> b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b -> f (b -> b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a7
h f (b -> b -> (b, b, b, b, b, b, b, b, b))
-> f b -> f (b -> (b, b, b, b, b, b, b, b, b))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a8
i f (b -> (b, b, b, b, b, b, b, b, b))
-> f b -> f (b, b, b, b, b, b, b, b, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a9
j
  {-# INLINE each #-}
instance Each (Complex a) (Complex b) a b where
  each :: (a -> f b) -> Complex a -> f (Complex b)
each a -> f b
f (a
a :+ a
b) = b -> b -> Complex b
forall a. a -> a -> Complex a
(:+) (b -> b -> Complex b) -> f b -> f (b -> Complex b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> Complex b) -> f b -> f (Complex b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
b
  {-# INLINE each #-}
instance (c ~ d) => Each (Map c a) (Map d b) a b where
  each :: (a -> f b) -> Map c a -> f (Map d b)
each = (a -> f b) -> Map c a -> f (Map d b)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed
  {-# INLINE each #-}
instance Each (IntMap a) (IntMap b) a b where
  each :: (a -> f b) -> IntMap a -> f (IntMap b)
each = (a -> f b) -> IntMap a -> f (IntMap b)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed
  {-# INLINE each #-}
instance (c ~ d) => Each (HashMap c a) (HashMap d b) a b where
  each :: (a -> f b) -> HashMap c a -> f (HashMap d b)
each = (a -> f b) -> HashMap c a -> f (HashMap d b)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed
  {-# INLINE each #-}
instance Each [a] [b] a b where
  each :: (a -> f b) -> [a] -> f [b]
each = (a -> f b) -> [a] -> f [b]
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed
  {-# INLINE each #-}
instance Each (NonEmpty a) (NonEmpty b) a b
instance Each (Identity a) (Identity b) a b
instance Each (Maybe a) (Maybe b) a b
instance (a~a', b~b') => Each (Either a a') (Either b b') a b where
  each :: (a -> f b) -> Either a a' -> f (Either b b')
each a -> f b
f (Left a
a)   = b -> Either b b'
forall a b. a -> Either a b
Left (b -> Either b b') -> f b -> f (Either b b')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
  each a -> f b
f (Right a'
a ) = b -> Either b b
forall a b. b -> Either a b
Right (b -> Either b b) -> f b -> f (Either b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a'
a
  {-# INLINE each #-}
instance Each (Seq a) (Seq b) a b where
  each :: (a -> f b) -> Seq a -> f (Seq b)
each = (a -> f b) -> Seq a -> f (Seq b)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed
  {-# INLINE each #-}
instance Each (Tree a) (Tree b) a b
instance Each (Vector.Vector a) (Vector.Vector b) a b where
  each :: (a -> f b) -> Vector a -> f (Vector b)
each = (a -> f b) -> Vector a -> f (Vector b)
forall (v :: * -> *) a (w :: * -> *) b.
(Vector v a, Vector w b) =>
IndexedTraversal Int (v a) (w b) a b
vectorTraverse
  {-# INLINE each #-}
instance (Prim a, Prim b) => Each (Prim.Vector a) (Prim.Vector b) a b where
  each :: (a -> f b) -> Vector a -> f (Vector b)
each = (a -> f b) -> Vector a -> f (Vector b)
forall (v :: * -> *) a (w :: * -> *) b.
(Vector v a, Vector w b) =>
IndexedTraversal Int (v a) (w b) a b
vectorTraverse
  {-# INLINE each #-}
instance (Storable a, Storable b) => Each (Storable.Vector a) (Storable.Vector b) a b where
  each :: (a -> f b) -> Vector a -> f (Vector b)
each = (a -> f b) -> Vector a -> f (Vector b)
forall (v :: * -> *) a (w :: * -> *) b.
(Vector v a, Vector w b) =>
IndexedTraversal Int (v a) (w b) a b
vectorTraverse
  {-# INLINE each #-}
instance (Unbox a, Unbox b) => Each (Unboxed.Vector a) (Unboxed.Vector b) a b where
  each :: (a -> f b) -> Vector a -> f (Vector b)
each = (a -> f b) -> Vector a -> f (Vector b)
forall (v :: * -> *) a (w :: * -> *) b.
(Vector v a, Vector w b) =>
IndexedTraversal Int (v a) (w b) a b
vectorTraverse
  {-# INLINE each #-}
instance (a ~ Char, b ~ Char) => Each StrictT.Text StrictT.Text a b where
  each :: (a -> f b) -> Text -> f Text
each = (a -> f b) -> Text -> f Text
forall t. IsText t => IndexedTraversal' Int t Char
text
  {-# INLINE each #-}
instance (a ~ Char, b ~ Char) => Each LazyT.Text LazyT.Text a b where
  each :: (a -> f b) -> Text -> f Text
each = (a -> f b) -> Text -> f Text
forall t. IsText t => IndexedTraversal' Int t Char
text
  {-# INLINE each #-}
instance (a ~ Word8, b ~ Word8) => Each StrictB.ByteString StrictB.ByteString a b where
  each :: (a -> f b) -> ByteString -> f ByteString
each = (a -> f b) -> ByteString -> f ByteString
IndexedTraversal' Int ByteString Word8
traversedStrictTree
  {-# INLINE each #-}
instance (a ~ Word8, b ~ Word8) => Each LazyB.ByteString LazyB.ByteString a b where
  each :: (a -> f b) -> ByteString -> f ByteString
each = (a -> f b) -> ByteString -> f ByteString
IndexedTraversal' Int64 ByteString Word8
traversedLazy
  {-# INLINE each #-}
instance (Ix i, i ~ j) => Each (Array i a) (Array j b) a b where
  each :: (a -> f b) -> Array i a -> f (Array j b)
each a -> f b
f Array i a
arr = (i, i) -> [(i, b)] -> Array i b
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Array i a -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds Array i a
arr) ([(i, b)] -> Array i b) -> f [(i, b)] -> f (Array i b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((i, a) -> f (i, b)) -> [(i, a)] -> f [(i, b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(i
i,a
a) -> (,) i
i (b -> (i, b)) -> f b -> f (i, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a) (Array i a -> [(i, a)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
IArray.assocs Array i a
arr)
  {-# INLINE each #-}
instance (Ix i, IArray UArray a, IArray UArray b, i ~ j) => Each (UArray i a) (UArray j b) a b where
  each :: (a -> f b) -> UArray i a -> f (UArray j b)
each a -> f b
f UArray i a
arr = (i, i) -> [(i, b)] -> UArray i b
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (UArray i a -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds UArray i a
arr) ([(i, b)] -> UArray i b) -> f [(i, b)] -> f (UArray i b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((i, a) -> f (i, b)) -> [(i, a)] -> f [(i, b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(i
i,a
a) -> (,) i
i (b -> (i, b)) -> f b -> f (i, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a) (UArray i a -> [(i, a)]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> [(i, e)]
IArray.assocs UArray i a
arr)
  {-# INLINE each #-}
instance (a ~ a', b ~ b') => Each (S.Either a a') (S.Either b b') a b where
    each :: (a -> f b) -> Either a a' -> f (Either b b')
each a -> f b
f (S.Left a
x)  = b -> Either b b'
forall a b. a -> Either a b
S.Left (b -> Either b b') -> f b -> f (Either b b')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
    each a -> f b
f (S.Right a'
x) = b -> Either b b
forall a b. b -> Either a b
S.Right (b -> Either b b) -> f b -> f (Either b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a'
x
    {-# INLINE each #-}
instance (a~a', b~b') => Each (S.Pair a a') (S.Pair b b') a b where
    each :: (a -> f b) -> Pair a a' -> f (Pair b b')
each a -> f b
f (a
a S.:!: a'
b) = b -> b -> Pair b b
forall a b. a -> b -> Pair a b
(S.:!:) (b -> b -> Pair b b) -> f b -> f (b -> Pair b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> Pair b b) -> f b -> f (Pair b b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a'
b
    {-# INLINE each #-}
instance Each (S.Maybe a) (S.Maybe b) a b
instance (a ~ a', b ~ b') => Each (S.These a a') (S.These b b') a b where
    each :: (a -> f b) -> These a a' -> f (These b b')
each a -> f b
f (S.This a
a)    = b -> These b b'
forall a b. a -> These a b
S.This (b -> These b b') -> f b -> f (These b b')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
    each a -> f b
f (S.That a'
b)    = b -> These b b
forall a b. b -> These a b
S.That (b -> These b b) -> f b -> f (These b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a'
b
    each a -> f b
f (S.These a
a a'
b) = b -> b -> These b b
forall a b. a -> b -> These a b
S.These (b -> b -> These b b) -> f b -> f (b -> These b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> These b b) -> f b -> f (These b b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a'
b
instance (a ~ a', b ~ b') => Each (These a a') (These b b') a b where
    each :: (a -> f b) -> These a a' -> f (These b b')
each a -> f b
f (This a
a)    = b -> These b b'
forall a b. a -> These a b
This (b -> These b b') -> f b -> f (These b b')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
    each a -> f b
f (That a'
b)    = b -> These b b
forall a b. b -> These a b
That (b -> These b b) -> f b -> f (These b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a'
b
    each a -> f b
f (These a
a a'
b) = b -> b -> These b b
forall a b. a -> b -> These a b
These (b -> b -> These b b) -> f b -> f (b -> These b b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (b -> These b b) -> f b -> f (These b b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
a'
b