{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
module Control.Lens.Reified where
import Control.Applicative
import Control.Arrow
import qualified Control.Category as Cat
import Control.Comonad
import Control.Lens.Fold
import Control.Lens.Getter
import Control.Lens.Internal.Indexed
import Control.Lens.Traversal (ignored)
import Control.Lens.Type
import Control.Monad
import Control.Monad.Reader.Class
import Data.Distributive
import Data.Foldable
import Data.Functor.Compose
import Data.Functor.Contravariant
import Data.Functor.Bind
import Data.Functor.Extend
import Data.Functor.Identity
import Data.Functor.Plus
import Data.Profunctor.Closed
import Data.Profunctor
import Data.Profunctor.Rep
import Data.Profunctor.Sieve
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
newtype ReifiedLens s t a b = Lens { forall s t a b. ReifiedLens s t a b -> Lens s t a b
runLens :: Lens s t a b }
type ReifiedLens' s a = ReifiedLens s s a a
newtype ReifiedIndexedLens i s t a b = IndexedLens { forall i s t a b.
ReifiedIndexedLens i s t a b -> IndexedLens i s t a b
runIndexedLens :: IndexedLens i s t a b }
type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a
newtype ReifiedIndexedTraversal i s t a b = IndexedTraversal { forall i s t a b.
ReifiedIndexedTraversal i s t a b -> IndexedTraversal i s t a b
runIndexedTraversal :: IndexedTraversal i s t a b }
type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a
newtype ReifiedTraversal s t a b = Traversal { forall s t a b. ReifiedTraversal s t a b -> Traversal s t a b
runTraversal :: Traversal s t a b }
type ReifiedTraversal' s a = ReifiedTraversal s s a a
newtype ReifiedGetter s a = Getter { forall s a. ReifiedGetter s a -> Getter s a
runGetter :: Getter s a }
instance Distributive (ReifiedGetter s) where
  distribute :: forall (f :: * -> *) a.
Functor f =>
f (ReifiedGetter s a) -> ReifiedGetter s (f a)
distribute f (ReifiedGetter s a)
as = Getter s (f a) -> ReifiedGetter s (f a)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s (f a) -> ReifiedGetter s (f a))
-> Getter s (f a) -> ReifiedGetter s (f a)
forall a b. (a -> b) -> a -> b
$ (s -> f a) -> Optic' (->) f s (f a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> f a) -> Optic' (->) f s (f a))
-> (s -> f a) -> Optic' (->) f s (f a)
forall a b. (a -> b) -> a -> b
$ \s
s -> (ReifiedGetter s a -> a) -> f (ReifiedGetter s a) -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Getter Getter s a
l) -> Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
l s
s) f (ReifiedGetter s a)
as
instance Functor (ReifiedGetter s) where
  fmap :: forall a b. (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b
fmap a -> b
f ReifiedGetter s a
l = Getter s b -> ReifiedGetter s b
forall s a. Getter s a -> ReifiedGetter s a
Getter (ReifiedGetter s a -> Getter s a
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter s a
l((a -> f a) -> s -> f s)
-> ((b -> f b) -> a -> f a) -> (b -> f b) -> s -> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f)
  {-# INLINE fmap #-}
instance Semigroup s => Extend (ReifiedGetter s) where
  duplicated :: forall a. ReifiedGetter s a -> ReifiedGetter s (ReifiedGetter s a)
duplicated (Getter Getter s a
l) = Getter s (ReifiedGetter s a) -> ReifiedGetter s (ReifiedGetter s a)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s (ReifiedGetter s a)
 -> ReifiedGetter s (ReifiedGetter s a))
-> Getter s (ReifiedGetter s a)
-> ReifiedGetter s (ReifiedGetter s a)
forall a b. (a -> b) -> a -> b
$ (s -> ReifiedGetter s a) -> Optic' (->) f s (ReifiedGetter s a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> ReifiedGetter s a) -> Optic' (->) f s (ReifiedGetter s a))
-> (s -> ReifiedGetter s a) -> Optic' (->) f s (ReifiedGetter s a)
forall a b. (a -> b) -> a -> b
$ \s
m -> Getter s a -> ReifiedGetter s a
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s a -> ReifiedGetter s a)
-> Getter s a -> ReifiedGetter s a
forall a b. (a -> b) -> a -> b
$ (s -> a) -> Optic' (->) f s a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> a) -> Optic' (->) f s a) -> (s -> a) -> Optic' (->) f s a
forall a b. (a -> b) -> a -> b
$ \s
n -> Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
l (s
m s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
n)
  {-# INLINE duplicated #-}
instance Monoid s => Comonad (ReifiedGetter s) where
  extract :: forall a. ReifiedGetter s a -> a
extract (Getter Getter s a
l) = Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
l s
forall a. Monoid a => a
mempty
  {-# INLINE extract #-}
  duplicate :: forall a. ReifiedGetter s a -> ReifiedGetter s (ReifiedGetter s a)
duplicate (Getter Getter s a
l) = Getter s (ReifiedGetter s a) -> ReifiedGetter s (ReifiedGetter s a)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s (ReifiedGetter s a)
 -> ReifiedGetter s (ReifiedGetter s a))
-> Getter s (ReifiedGetter s a)
-> ReifiedGetter s (ReifiedGetter s a)
forall a b. (a -> b) -> a -> b
$ (s -> ReifiedGetter s a) -> Optic' (->) f s (ReifiedGetter s a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> ReifiedGetter s a) -> Optic' (->) f s (ReifiedGetter s a))
-> (s -> ReifiedGetter s a) -> Optic' (->) f s (ReifiedGetter s a)
forall a b. (a -> b) -> a -> b
$ \s
m -> Getter s a -> ReifiedGetter s a
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s a -> ReifiedGetter s a)
-> Getter s a -> ReifiedGetter s a
forall a b. (a -> b) -> a -> b
$ (s -> a) -> Optic' (->) f s a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> a) -> Optic' (->) f s a) -> (s -> a) -> Optic' (->) f s a
forall a b. (a -> b) -> a -> b
$ \s
n -> Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
l (s -> s -> s
forall a. Monoid a => a -> a -> a
mappend s
m s
n)
  {-# INLINE duplicate #-}
instance Monoid s => ComonadApply (ReifiedGetter s) where
  Getter Getter s (a -> b)
mf <@> :: forall a b.
ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b
<@> Getter Getter s a
ma = Getter s b -> ReifiedGetter s b
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s b -> ReifiedGetter s b)
-> Getter s b -> ReifiedGetter s b
forall a b. (a -> b) -> a -> b
$ (s -> b) -> Optic' (->) f s b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> b) -> Optic' (->) f s b) -> (s -> b) -> Optic' (->) f s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (a -> b) s (a -> b) -> s -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (a -> b) s (a -> b)
Getter s (a -> b)
mf s
s (Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
ma s
s)
  {-# INLINE (<@>) #-}
  ReifiedGetter s a
m <@ :: forall a b.
ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a
<@ ReifiedGetter s b
_ = ReifiedGetter s a
m
  {-# INLINE (<@) #-}
  ReifiedGetter s a
_ @> :: forall a b.
ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b
@> ReifiedGetter s b
m = ReifiedGetter s b
m
  {-# INLINE (@>) #-}
instance Apply (ReifiedGetter s) where
  Getter Getter s (a -> b)
mf <.> :: forall a b.
ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b
<.> Getter Getter s a
ma = Getter s b -> ReifiedGetter s b
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s b -> ReifiedGetter s b)
-> Getter s b -> ReifiedGetter s b
forall a b. (a -> b) -> a -> b
$ (s -> b) -> Optic' (->) f s b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> b) -> Optic' (->) f s b) -> (s -> b) -> Optic' (->) f s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (a -> b) s (a -> b) -> s -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (a -> b) s (a -> b)
Getter s (a -> b)
mf s
s (Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
ma s
s)
  {-# INLINE (<.>) #-}
  ReifiedGetter s a
m <. :: forall a b.
ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a
<. ReifiedGetter s b
_ = ReifiedGetter s a
m
  {-# INLINE (<.) #-}
  ReifiedGetter s a
_ .> :: forall a b.
ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b
.> ReifiedGetter s b
m = ReifiedGetter s b
m
  {-# INLINE (.>) #-}
instance Applicative (ReifiedGetter s) where
  pure :: forall a. a -> ReifiedGetter s a
pure a
a = Getter s a -> ReifiedGetter s a
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s a -> ReifiedGetter s a)
-> Getter s a -> ReifiedGetter s a
forall a b. (a -> b) -> a -> b
$ (s -> a) -> Optic' (->) f s a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> a) -> Optic' (->) f s a) -> (s -> a) -> Optic' (->) f s a
forall a b. (a -> b) -> a -> b
$ \s
_ -> a
a
  {-# INLINE pure #-}
  Getter Getter s (a -> b)
mf <*> :: forall a b.
ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b
<*> Getter Getter s a
ma = Getter s b -> ReifiedGetter s b
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s b -> ReifiedGetter s b)
-> Getter s b -> ReifiedGetter s b
forall a b. (a -> b) -> a -> b
$ (s -> b) -> Optic' (->) f s b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> b) -> Optic' (->) f s b) -> (s -> b) -> Optic' (->) f s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (a -> b) s (a -> b) -> s -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (a -> b) s (a -> b)
Getter s (a -> b)
mf s
s (Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
ma s
s)
  {-# INLINE (<*>) #-}
  ReifiedGetter s a
m <* :: forall a b.
ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a
<* ReifiedGetter s b
_ = ReifiedGetter s a
m
  {-# INLINE (<*) #-}
  ReifiedGetter s a
_ *> :: forall a b.
ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b
*> ReifiedGetter s b
m = ReifiedGetter s b
m
  {-# INLINE (*>) #-}
instance Bind (ReifiedGetter s) where
  Getter Getter s a
ma >>- :: forall a b.
ReifiedGetter s a -> (a -> ReifiedGetter s b) -> ReifiedGetter s b
>>- a -> ReifiedGetter s b
f = Getter s b -> ReifiedGetter s b
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s b -> ReifiedGetter s b)
-> Getter s b -> ReifiedGetter s b
forall a b. (a -> b) -> a -> b
$ (s -> b) -> Optic' (->) f s b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> b) -> Optic' (->) f s b) -> (s -> b) -> Optic' (->) f s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting b s b -> s -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (ReifiedGetter s b -> Getter s b
forall s a. ReifiedGetter s a -> Getter s a
runGetter (a -> ReifiedGetter s b
f (Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
ma s
s))) s
s
  {-# INLINE (>>-) #-}
instance Monad (ReifiedGetter s) where
  return :: forall a. a -> ReifiedGetter s a
return = a -> ReifiedGetter s a
forall a. a -> ReifiedGetter s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  Getter Getter s a
ma >>= :: forall a b.
ReifiedGetter s a -> (a -> ReifiedGetter s b) -> ReifiedGetter s b
>>= a -> ReifiedGetter s b
f = Getter s b -> ReifiedGetter s b
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter s b -> ReifiedGetter s b)
-> Getter s b -> ReifiedGetter s b
forall a b. (a -> b) -> a -> b
$ (s -> b) -> Optic' (->) f s b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((s -> b) -> Optic' (->) f s b) -> (s -> b) -> Optic' (->) f s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting b s b -> s -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (ReifiedGetter s b -> Getter s b
forall s a. ReifiedGetter s a -> Getter s a
runGetter (a -> ReifiedGetter s b
f (Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting a s a
Getter s a
ma s
s))) s
s
  {-# INLINE (>>=) #-}
instance MonadReader s (ReifiedGetter s) where
  ask :: ReifiedGetter s s
ask = Getter s s -> ReifiedGetter s s
forall s a. Getter s a -> ReifiedGetter s a
Getter (s -> f s) -> s -> f s
forall a. a -> a
Getter s s
id
  {-# INLINE ask #-}
  local :: forall a. (s -> s) -> ReifiedGetter s a -> ReifiedGetter s a
local s -> s
f ReifiedGetter s a
m = Getter s a -> ReifiedGetter s a
forall s a. Getter s a -> ReifiedGetter s a
Getter ((s -> s) -> (s -> f s) -> s -> f s
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to s -> s
f ((s -> f s) -> s -> f s)
-> ((a -> f a) -> s -> f s) -> (a -> f a) -> s -> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedGetter s a -> Getter s a
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter s a
m)
  {-# INLINE local #-}
instance Profunctor ReifiedGetter where
  dimap :: forall a b c d.
(a -> b) -> (c -> d) -> ReifiedGetter b c -> ReifiedGetter a d
dimap a -> b
f c -> d
g ReifiedGetter b c
l = Getter a d -> ReifiedGetter a d
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter a d -> ReifiedGetter a d)
-> Getter a d -> ReifiedGetter a d
forall a b. (a -> b) -> a -> b
$ (a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f((b -> f b) -> a -> f a)
-> ((d -> f d) -> b -> f b) -> (d -> f d) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l((c -> f c) -> b -> f b)
-> ((d -> f d) -> c -> f c) -> (d -> f d) -> b -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(c -> d) -> (d -> f d) -> c -> f c
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to c -> d
g
  {-# INLINE dimap #-}
  lmap :: forall a b c. (a -> b) -> ReifiedGetter b c -> ReifiedGetter a c
lmap a -> b
g ReifiedGetter b c
l    = Getter a c -> ReifiedGetter a c
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter a c -> ReifiedGetter a c)
-> Getter a c -> ReifiedGetter a c
forall a b. (a -> b) -> a -> b
$ (a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
g((b -> f b) -> a -> f a)
-> ((c -> f c) -> b -> f b) -> (c -> f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l
  {-# INLINE lmap #-}
  rmap :: forall b c a. (b -> c) -> ReifiedGetter a b -> ReifiedGetter a c
rmap b -> c
f ReifiedGetter a b
l    = Getter a c -> ReifiedGetter a c
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter a c -> ReifiedGetter a c)
-> Getter a c -> ReifiedGetter a c
forall a b. (a -> b) -> a -> b
$ ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
l((b -> f b) -> a -> f a)
-> ((c -> f c) -> b -> f b) -> (c -> f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(b -> c) -> (c -> f c) -> b -> f b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to b -> c
f
  {-# INLINE rmap #-}
instance Closed ReifiedGetter where
  closed :: forall a b x. ReifiedGetter a b -> ReifiedGetter (x -> a) (x -> b)
closed ReifiedGetter a b
l = Getter (x -> a) (x -> b) -> ReifiedGetter (x -> a) (x -> b)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (x -> a) (x -> b) -> ReifiedGetter (x -> a) (x -> b))
-> Getter (x -> a) (x -> b) -> ReifiedGetter (x -> a) (x -> b)
forall a b. (a -> b) -> a -> b
$ ((x -> a) -> x -> b) -> Optic' (->) f (x -> a) (x -> b)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (((x -> a) -> x -> b) -> Optic' (->) f (x -> a) (x -> b))
-> ((x -> a) -> x -> b) -> Optic' (->) f (x -> a) (x -> b)
forall a b. (a -> b) -> a -> b
$ \x -> a
f -> Getting b a b -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
l) (a -> b) -> (x -> a) -> x -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> a
f
instance Cosieve ReifiedGetter Identity where
  cosieve :: forall a b. ReifiedGetter a b -> Identity a -> b
cosieve (Getter Getter a b
l) = Getting b a b -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting b a b
Getter a b
l (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 Corepresentable ReifiedGetter where
  type Corep ReifiedGetter = Identity
  cotabulate :: forall d c. (Corep ReifiedGetter d -> c) -> ReifiedGetter d c
cotabulate Corep ReifiedGetter d -> c
f = Getter d c -> ReifiedGetter d c
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter d c -> ReifiedGetter d c)
-> Getter d c -> ReifiedGetter d c
forall a b. (a -> b) -> a -> b
$ (d -> c) -> (c -> f c) -> d -> f d
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (Identity d -> c
Corep ReifiedGetter d -> c
f (Identity d -> c) -> (d -> Identity d) -> d -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Identity d
forall a. a -> Identity a
Identity)
instance Sieve ReifiedGetter Identity where
  sieve :: forall a b. ReifiedGetter a b -> a -> Identity b
sieve (Getter Getter a b
l) = b -> Identity b
forall a. a -> Identity a
Identity (b -> Identity b) -> (a -> b) -> a -> Identity b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting b a b -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting b a b
Getter a b
l
instance Representable ReifiedGetter where
  type Rep ReifiedGetter = Identity
  tabulate :: forall d c. (d -> Rep ReifiedGetter c) -> ReifiedGetter d c
tabulate d -> Rep ReifiedGetter c
f = Getter d c -> ReifiedGetter d c
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter d c -> ReifiedGetter d c)
-> Getter d c -> ReifiedGetter d c
forall a b. (a -> b) -> a -> b
$ (d -> c) -> (c -> f c) -> d -> f d
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (Identity c -> c
forall a. Identity a -> a
runIdentity (Identity c -> c) -> (d -> Identity c) -> d -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Identity c
d -> Rep ReifiedGetter c
f)
instance Costrong ReifiedGetter where
  unfirst :: forall a d b. ReifiedGetter (a, d) (b, d) -> ReifiedGetter a b
unfirst ReifiedGetter (a, d) (b, d)
l = Getter a b -> ReifiedGetter a b
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter a b -> ReifiedGetter a b)
-> Getter a b -> ReifiedGetter a b
forall a b. (a -> b) -> a -> b
$ (a -> b) -> Optic' (->) f a b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((a -> b) -> Optic' (->) f a b) -> (a -> b) -> Optic' (->) f a b
forall a b. (a -> b) -> a -> b
$ ((a, d) -> (b, d)) -> a -> b
forall a d b. ((a, d) -> (b, d)) -> a -> b
forall (p :: * -> * -> *) a d b.
Costrong p =>
p (a, d) (b, d) -> p a b
unfirst (((a, d) -> (b, d)) -> a -> b) -> ((a, d) -> (b, d)) -> a -> b
forall a b. (a -> b) -> a -> b
$ Getting (b, d) (a, d) (b, d) -> (a, d) -> (b, d)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (ReifiedGetter (a, d) (b, d) -> Getter (a, d) (b, d)
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter (a, d) (b, d)
l)
instance Conjoined ReifiedGetter
instance Strong ReifiedGetter where
  first' :: forall a b c. ReifiedGetter a b -> ReifiedGetter (a, c) (b, c)
first' ReifiedGetter a b
l = Getter (a, c) (b, c) -> ReifiedGetter (a, c) (b, c)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (a, c) (b, c) -> ReifiedGetter (a, c) (b, c))
-> Getter (a, c) (b, c) -> ReifiedGetter (a, c) (b, c)
forall a b. (a -> b) -> a -> b
$ \(b, c) -> f (b, c)
f (a
s,c
c) ->
    f a -> f (a, c)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (a, c)) -> f a -> f (a, c)
forall a b. (a -> b) -> a -> b
$ ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
l ((b -> (b, c))
-> (f (b, c) -> f b) -> ((b, c) -> f (b, c)) -> b -> f b
forall a b c d. (a -> b) -> (c -> d) -> (b -> c) -> a -> d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((b -> c -> (b, c)) -> c -> b -> (b, c)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) c
c) f (b, c) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (b, c) -> f (b, c)
f) a
s
  {-# INLINE first' #-}
  second' :: forall a b c. ReifiedGetter a b -> ReifiedGetter (c, a) (c, b)
second' ReifiedGetter a b
l = Getter (c, a) (c, b) -> ReifiedGetter (c, a) (c, b)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (c, a) (c, b) -> ReifiedGetter (c, a) (c, b))
-> Getter (c, a) (c, b) -> ReifiedGetter (c, a) (c, b)
forall a b. (a -> b) -> a -> b
$ \(c, b) -> f (c, b)
f (c
c,a
s) ->
    f a -> f (c, a)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (c, a)) -> f a -> f (c, a)
forall a b. (a -> b) -> a -> b
$ ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
l ((b -> (c, b))
-> (f (c, b) -> f b) -> ((c, b) -> f (c, b)) -> b -> f b
forall a b c d. (a -> b) -> (c -> d) -> (b -> c) -> a -> d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((,) c
c) f (c, b) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (c, b) -> f (c, b)
f) a
s
  {-# INLINE second' #-}
instance Choice ReifiedGetter where
  left' :: forall a b c.
ReifiedGetter a b -> ReifiedGetter (Either a c) (Either b c)
left' ReifiedGetter a b
l = Getter (Either a c) (Either b c)
-> ReifiedGetter (Either a c) (Either b c)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (Either a c) (Either b c)
 -> ReifiedGetter (Either a c) (Either b c))
-> Getter (Either a c) (Either b c)
-> ReifiedGetter (Either a c) (Either b c)
forall a b. (a -> b) -> a -> b
$ (Either a c -> Either b c)
-> Optic' (->) f (Either a c) (Either b c)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Either a c -> Either b c)
 -> Optic' (->) f (Either a c) (Either b c))
-> (Either a c -> Either b c)
-> Optic' (->) f (Either a c) (Either b c)
forall a b. (a -> b) -> a -> b
$ (a -> b) -> Either a c -> Either b c
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either a c) (Either b c)
left' ((a -> b) -> Either a c -> Either b c)
-> (a -> b) -> Either a c -> Either b c
forall a b. (a -> b) -> a -> b
$ Getting b a b -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting b a b -> a -> b) -> Getting b a b -> a -> b
forall a b. (a -> b) -> a -> b
$ ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
l
  {-# INLINE left' #-}
  right' :: forall a b c.
ReifiedGetter a b -> ReifiedGetter (Either c a) (Either c b)
right' ReifiedGetter a b
l = Getter (Either c a) (Either c b)
-> ReifiedGetter (Either c a) (Either c b)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (Either c a) (Either c b)
 -> ReifiedGetter (Either c a) (Either c b))
-> Getter (Either c a) (Either c b)
-> ReifiedGetter (Either c a) (Either c b)
forall a b. (a -> b) -> a -> b
$ (Either c a -> Either c b)
-> Optic' (->) f (Either c a) (Either c b)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Either c a -> Either c b)
 -> Optic' (->) f (Either c a) (Either c b))
-> (Either c a -> Either c b)
-> Optic' (->) f (Either c a) (Either c b)
forall a b. (a -> b) -> a -> b
$ (a -> b) -> Either c a -> Either c b
forall a b c. (a -> b) -> Either c a -> Either c b
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right' ((a -> b) -> Either c a -> Either c b)
-> (a -> b) -> Either c a -> Either c b
forall a b. (a -> b) -> a -> b
$ Getting b a b -> a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting b a b -> a -> b) -> Getting b a b -> a -> b
forall a b. (a -> b) -> a -> b
$ ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
l
  {-# INLINE right' #-}
instance Cat.Category ReifiedGetter where
  id :: forall s. ReifiedGetter s s
id = Getter a a -> ReifiedGetter a a
forall s a. Getter s a -> ReifiedGetter s a
Getter (a -> f a) -> a -> f a
forall a. a -> a
Getter a a
id
  ReifiedGetter b c
l . :: forall b c a.
ReifiedGetter b c -> ReifiedGetter a b -> ReifiedGetter a c
. ReifiedGetter a b
r = Getter a c -> ReifiedGetter a c
forall s a. Getter s a -> ReifiedGetter s a
Getter (ReifiedGetter a b -> Getter a b
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter a b
r((b -> f b) -> a -> f a)
-> ((c -> f c) -> b -> f b) -> (c -> f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l)
  {-# INLINE (.) #-}
instance Arrow ReifiedGetter where
  arr :: forall s a. (s -> a) -> ReifiedGetter s a
arr b -> c
f = Getter b c -> ReifiedGetter b c
forall s a. Getter s a -> ReifiedGetter s a
Getter ((b -> c) -> (c -> f c) -> b -> f b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to b -> c
f)
  {-# INLINE arr #-}
  first :: forall a b c. ReifiedGetter a b -> ReifiedGetter (a, c) (b, c)
first ReifiedGetter b c
l = Getter (b, d) (c, d) -> ReifiedGetter (b, d) (c, d)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (b, d) (c, d) -> ReifiedGetter (b, d) (c, d))
-> Getter (b, d) (c, d) -> ReifiedGetter (b, d) (c, d)
forall a b. (a -> b) -> a -> b
$ ((b, d) -> (c, d)) -> Optic' (->) f (b, d) (c, d)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (((b, d) -> (c, d)) -> Optic' (->) f (b, d) (c, d))
-> ((b, d) -> (c, d)) -> Optic' (->) f (b, d) (c, d)
forall a b. (a -> b) -> a -> b
$ (b -> c) -> (b, d) -> (c, d)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first ((b -> c) -> (b, d) -> (c, d)) -> (b -> c) -> (b, d) -> (c, d)
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting c b c -> b -> c) -> Getting c b c -> b -> c
forall a b. (a -> b) -> a -> b
$ ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l
  {-# INLINE first #-}
  second :: forall a b c. ReifiedGetter a b -> ReifiedGetter (c, a) (c, b)
second ReifiedGetter b c
l = Getter (d, b) (d, c) -> ReifiedGetter (d, b) (d, c)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (d, b) (d, c) -> ReifiedGetter (d, b) (d, c))
-> Getter (d, b) (d, c) -> ReifiedGetter (d, b) (d, c)
forall a b. (a -> b) -> a -> b
$ ((d, b) -> (d, c)) -> Optic' (->) f (d, b) (d, c)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (((d, b) -> (d, c)) -> Optic' (->) f (d, b) (d, c))
-> ((d, b) -> (d, c)) -> Optic' (->) f (d, b) (d, c)
forall a b. (a -> b) -> a -> b
$ (b -> c) -> (d, b) -> (d, c)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ((b -> c) -> (d, b) -> (d, c)) -> (b -> c) -> (d, b) -> (d, c)
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting c b c -> b -> c) -> Getting c b c -> b -> c
forall a b. (a -> b) -> a -> b
$ ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l
  {-# INLINE second #-}
  Getter Getter b c
l *** :: forall b c b' c'.
ReifiedGetter b c
-> ReifiedGetter b' c' -> ReifiedGetter (b, b') (c, c')
*** Getter Getter b' c'
r = Getter (b, b') (c, c') -> ReifiedGetter (b, b') (c, c')
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (b, b') (c, c') -> ReifiedGetter (b, b') (c, c'))
-> Getter (b, b') (c, c') -> ReifiedGetter (b, b') (c, c')
forall a b. (a -> b) -> a -> b
$ ((b, b') -> (c, c')) -> Optic' (->) f (b, b') (c, c')
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (((b, b') -> (c, c')) -> Optic' (->) f (b, b') (c, c'))
-> ((b, b') -> (c, c')) -> Optic' (->) f (b, b') (c, c')
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c b c
Getter b c
l (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall b c b' c'. (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** Getting c' b' c' -> b' -> c'
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c' b' c'
Getter b' c'
r
  {-# INLINE (***) #-}
  Getter Getter b c
l &&& :: forall b c c'.
ReifiedGetter b c -> ReifiedGetter b c' -> ReifiedGetter b (c, c')
&&& Getter Getter b c'
r = Getter b (c, c') -> ReifiedGetter b (c, c')
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter b (c, c') -> ReifiedGetter b (c, c'))
-> Getter b (c, c') -> ReifiedGetter b (c, c')
forall a b. (a -> b) -> a -> b
$ (b -> (c, c')) -> Optic' (->) f b (c, c')
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((b -> (c, c')) -> Optic' (->) f b (c, c'))
-> (b -> (c, c')) -> Optic' (->) f b (c, c')
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c b c
Getter b c
l (b -> c) -> (b -> c') -> b -> (c, c')
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Getting c' b c' -> b -> c'
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c' b c'
Getter b c'
r
  {-# INLINE (&&&) #-}
instance ArrowApply ReifiedGetter where
  app :: forall b c. ReifiedGetter (ReifiedGetter b c, b) c
app = Getter (ReifiedGetter b c, b) c
-> ReifiedGetter (ReifiedGetter b c, b) c
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (ReifiedGetter b c, b) c
 -> ReifiedGetter (ReifiedGetter b c, b) c)
-> Getter (ReifiedGetter b c, b) c
-> ReifiedGetter (ReifiedGetter b c, b) c
forall a b. (a -> b) -> a -> b
$ ((ReifiedGetter b c, b) -> c)
-> Optic' (->) f (ReifiedGetter b c, b) c
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (((ReifiedGetter b c, b) -> c)
 -> Optic' (->) f (ReifiedGetter b c, b) c)
-> ((ReifiedGetter b c, b) -> c)
-> Optic' (->) f (ReifiedGetter b c, b) c
forall a b. (a -> b) -> a -> b
$ \(Getter Getter b c
bc, b
b) -> Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c b c
Getter b c
bc b
b
  {-# INLINE app #-}
instance ArrowChoice ReifiedGetter where
  left :: forall a b c.
ReifiedGetter a b -> ReifiedGetter (Either a c) (Either b c)
left ReifiedGetter b c
l = Getter (Either b d) (Either c d)
-> ReifiedGetter (Either b d) (Either c d)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (Either b d) (Either c d)
 -> ReifiedGetter (Either b d) (Either c d))
-> Getter (Either b d) (Either c d)
-> ReifiedGetter (Either b d) (Either c d)
forall a b. (a -> b) -> a -> b
$ (Either b d -> Either c d)
-> Optic' (->) f (Either b d) (Either c d)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Either b d -> Either c d)
 -> Optic' (->) f (Either b d) (Either c d))
-> (Either b d -> Either c d)
-> Optic' (->) f (Either b d) (Either c d)
forall a b. (a -> b) -> a -> b
$ (b -> c) -> Either b d -> Either c d
forall a b c. (a -> b) -> Either a c -> Either b c
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left ((b -> c) -> Either b d -> Either c d)
-> (b -> c) -> Either b d -> Either c d
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting c b c -> b -> c) -> Getting c b c -> b -> c
forall a b. (a -> b) -> a -> b
$ ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l
  {-# INLINE left #-}
  right :: forall a b c.
ReifiedGetter a b -> ReifiedGetter (Either c a) (Either c b)
right ReifiedGetter b c
l = Getter (Either d b) (Either d c)
-> ReifiedGetter (Either d b) (Either d c)
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (Either d b) (Either d c)
 -> ReifiedGetter (Either d b) (Either d c))
-> Getter (Either d b) (Either d c)
-> ReifiedGetter (Either d b) (Either d c)
forall a b. (a -> b) -> a -> b
$ (Either d b -> Either d c)
-> Optic' (->) f (Either d b) (Either d c)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Either d b -> Either d c)
 -> Optic' (->) f (Either d b) (Either d c))
-> (Either d b -> Either d c)
-> Optic' (->) f (Either d b) (Either d c)
forall a b. (a -> b) -> a -> b
$ (b -> c) -> Either d b -> Either d c
forall a b c. (a -> b) -> Either c a -> Either c b
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either d b) (Either d c)
right ((b -> c) -> Either d b -> Either d c)
-> (b -> c) -> Either d b -> Either d c
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting c b c -> b -> c) -> Getting c b c -> b -> c
forall a b. (a -> b) -> a -> b
$ ReifiedGetter b c -> Getter b c
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter b c
l
  {-# INLINE right #-}
  Getter Getter b c
l +++ :: forall b c b' c'.
ReifiedGetter b c
-> ReifiedGetter b' c' -> ReifiedGetter (Either b b') (Either c c')
+++ Getter Getter b' c'
r = Getter (Either b b') (Either c c')
-> ReifiedGetter (Either b b') (Either c c')
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (Either b b') (Either c c')
 -> ReifiedGetter (Either b b') (Either c c'))
-> Getter (Either b b') (Either c c')
-> ReifiedGetter (Either b b') (Either c c')
forall a b. (a -> b) -> a -> b
$ (Either b b' -> Either c c')
-> Optic' (->) f (Either b b') (Either c c')
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Either b b' -> Either c c')
 -> Optic' (->) f (Either b b') (Either c c'))
-> (Either b b' -> Either c c')
-> Optic' (->) f (Either b b') (Either c c')
forall a b. (a -> b) -> a -> b
$ Getting c b c -> b -> c
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c b c
Getter b c
l (b -> c) -> (b' -> c') -> Either b b' -> Either c c'
forall b c b' c'.
(b -> c) -> (b' -> c') -> Either b b' -> Either c c'
forall (a :: * -> * -> *) b c b' c'.
ArrowChoice a =>
a b c -> a b' c' -> a (Either b b') (Either c c')
+++ Getting c' b' c' -> b' -> c'
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting c' b' c'
Getter b' c'
r
  {-# INLINE (+++) #-}
  Getter Getter b d
l ||| :: forall b d c.
ReifiedGetter b d
-> ReifiedGetter c d -> ReifiedGetter (Either b c) d
||| Getter Getter c d
r = Getter (Either b c) d -> ReifiedGetter (Either b c) d
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter (Either b c) d -> ReifiedGetter (Either b c) d)
-> Getter (Either b c) d -> ReifiedGetter (Either b c) d
forall a b. (a -> b) -> a -> b
$ (Either b c -> d) -> Optic' (->) f (Either b c) d
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Either b c -> d) -> Optic' (->) f (Either b c) d)
-> (Either b c -> d) -> Optic' (->) f (Either b c) d
forall a b. (a -> b) -> a -> b
$ Getting d b d -> b -> d
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting d b d
Getter b d
l (b -> d) -> (c -> d) -> Either b c -> d
forall b d c. (b -> d) -> (c -> d) -> Either b c -> d
forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| Getting d c d -> c -> d
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting d c d
Getter c d
r
  {-# INLINE (|||) #-}
instance ArrowLoop ReifiedGetter where
  loop :: forall a d b. ReifiedGetter (a, d) (b, d) -> ReifiedGetter a b
loop ReifiedGetter (b, d) (c, d)
l = Getter b c -> ReifiedGetter b c
forall s a. Getter s a -> ReifiedGetter s a
Getter (Getter b c -> ReifiedGetter b c)
-> Getter b c -> ReifiedGetter b c
forall a b. (a -> b) -> a -> b
$ (b -> c) -> Optic' (->) f b c
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((b -> c) -> Optic' (->) f b c) -> (b -> c) -> Optic' (->) f b c
forall a b. (a -> b) -> a -> b
$ ((b, d) -> (c, d)) -> b -> c
forall a d b. ((a, d) -> (b, d)) -> a -> b
forall (a :: * -> * -> *) b d c.
ArrowLoop a =>
a (b, d) (c, d) -> a b c
loop (((b, d) -> (c, d)) -> b -> c) -> ((b, d) -> (c, d)) -> b -> c
forall a b. (a -> b) -> a -> b
$ Getting (c, d) (b, d) (c, d) -> (b, d) -> (c, d)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting (c, d) (b, d) (c, d) -> (b, d) -> (c, d))
-> Getting (c, d) (b, d) (c, d) -> (b, d) -> (c, d)
forall a b. (a -> b) -> a -> b
$ ReifiedGetter (b, d) (c, d) -> Getter (b, d) (c, d)
forall s a. ReifiedGetter s a -> Getter s a
runGetter ReifiedGetter (b, d) (c, d)
l
  {-# INLINE loop #-}
newtype ReifiedIndexedGetter i s a = IndexedGetter { forall i s a. ReifiedIndexedGetter i s a -> IndexedGetter i s a
runIndexedGetter :: IndexedGetter i s a }
instance Profunctor (ReifiedIndexedGetter i) where
  dimap :: forall a b c d.
(a -> b)
-> (c -> d)
-> ReifiedIndexedGetter i b c
-> ReifiedIndexedGetter i a d
dimap a -> b
f c -> d
g ReifiedIndexedGetter i b c
l = IndexedGetter i a d -> ReifiedIndexedGetter i a d
forall i s a. IndexedGetter i s a -> ReifiedIndexedGetter i s a
IndexedGetter ((a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f ((b -> f b) -> a -> f a)
-> (p d (f d) -> b -> f b) -> p d (f d) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedIndexedGetter i b c -> IndexedGetter i b c
forall i s a. ReifiedIndexedGetter i s a -> IndexedGetter i s a
runIndexedGetter ReifiedIndexedGetter i b c
l (p c (f c) -> b -> f b)
-> (p d (f d) -> p c (f c)) -> p d (f d) -> b -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (c -> d) -> p d (f d) -> p c (f c)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to c -> d
g)
  {-# INLINE dimap #-}
instance Sieve (ReifiedIndexedGetter i) ((,) i) where
  sieve :: forall a b. ReifiedIndexedGetter i a b -> a -> (i, b)
sieve (IndexedGetter IndexedGetter i a b
l) = IndexedGetting i (i, b) a b -> a -> (i, b)
forall s (m :: * -> *) i a.
MonadReader s m =>
IndexedGetting i (i, a) s a -> m (i, a)
iview IndexedGetting i (i, b) a b
IndexedGetter i a b
l
  {-# INLINE sieve #-}
instance Representable (ReifiedIndexedGetter i) where
  type Rep (ReifiedIndexedGetter i) = (,) i
  tabulate :: forall d c.
(d -> Rep (ReifiedIndexedGetter i) c) -> ReifiedIndexedGetter i d c
tabulate d -> Rep (ReifiedIndexedGetter i) c
f = IndexedGetter i d c -> ReifiedIndexedGetter i d c
forall i s a. IndexedGetter i s a -> ReifiedIndexedGetter i s a
IndexedGetter (IndexedGetter i d c -> ReifiedIndexedGetter i d c)
-> IndexedGetter i d c -> ReifiedIndexedGetter i d c
forall a b. (a -> b) -> a -> b
$ (d -> (i, c)) -> Over' p f d c
forall i (p :: * -> * -> *) (f :: * -> *) s a.
(Indexable i p, Contravariant f) =>
(s -> (i, a)) -> Over' p f s a
ito d -> (i, c)
d -> Rep (ReifiedIndexedGetter i) c
f
  {-# INLINE tabulate #-}
instance Strong (ReifiedIndexedGetter i) where
  first' :: forall a b c.
ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i (a, c) (b, c)
first' ReifiedIndexedGetter i a b
l = IndexedGetter i (a, c) (b, c)
-> ReifiedIndexedGetter i (a, c) (b, c)
forall i s a. IndexedGetter i s a -> ReifiedIndexedGetter i s a
IndexedGetter (IndexedGetter i (a, c) (b, c)
 -> ReifiedIndexedGetter i (a, c) (b, c))
-> IndexedGetter i (a, c) (b, c)
-> ReifiedIndexedGetter i (a, c) (b, c)
forall a b. (a -> b) -> a -> b
$ \p (b, c) (f (b, c))
f (a
s,c
c) ->
    f a -> f (a, c)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (a, c)) -> f a -> f (a, c)
forall a b. (a -> b) -> a -> b
$ ReifiedIndexedGetter i a b -> IndexedGetter i a b
forall i s a. ReifiedIndexedGetter i s a -> IndexedGetter i s a
runIndexedGetter ReifiedIndexedGetter i a b
l ((b -> (b, c))
-> (f (b, c) -> f b) -> p (b, c) (f (b, c)) -> p b (f b)
forall a b c d. (a -> b) -> (c -> d) -> p b c -> p a d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((b -> c -> (b, c)) -> c -> b -> (b, c)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) c
c) f (b, c) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom p (b, c) (f (b, c))
f) a
s
  {-# INLINE first' #-}
  second' :: forall a b c.
ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i (c, a) (c, b)
second' ReifiedIndexedGetter i a b
l = IndexedGetter i (c, a) (c, b)
-> ReifiedIndexedGetter i (c, a) (c, b)
forall i s a. IndexedGetter i s a -> ReifiedIndexedGetter i s a
IndexedGetter (IndexedGetter i (c, a) (c, b)
 -> ReifiedIndexedGetter i (c, a) (c, b))
-> IndexedGetter i (c, a) (c, b)
-> ReifiedIndexedGetter i (c, a) (c, b)
forall a b. (a -> b) -> a -> b
$ \p (c, b) (f (c, b))
f (c
c,a
s) ->
    f a -> f (c, a)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (c, a)) -> f a -> f (c, a)
forall a b. (a -> b) -> a -> b
$ ReifiedIndexedGetter i a b -> IndexedGetter i a b
forall i s a. ReifiedIndexedGetter i s a -> IndexedGetter i s a
runIndexedGetter ReifiedIndexedGetter i a b
l ((b -> (c, b))
-> (f (c, b) -> f b) -> p (c, b) (f (c, b)) -> p b (f b)
forall a b c d. (a -> b) -> (c -> d) -> p b c -> p a d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((,) c
c) f (c, b) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom p (c, b) (f (c, b))
f) a
s
  {-# INLINE second' #-}
instance Functor (ReifiedIndexedGetter i s) where
  fmap :: forall a b.
(a -> b)
-> ReifiedIndexedGetter i s a -> ReifiedIndexedGetter i s b
fmap a -> b
f ReifiedIndexedGetter i s a
l = IndexedGetter i s b -> ReifiedIndexedGetter i s b
forall i s a. IndexedGetter i s a -> ReifiedIndexedGetter i s a
IndexedGetter (ReifiedIndexedGetter i s a -> IndexedGetter i s a
forall i s a. ReifiedIndexedGetter i s a -> IndexedGetter i s a
runIndexedGetter ReifiedIndexedGetter i s a
l(p a (f a) -> s -> f s)
-> (p b (f b) -> p a (f a)) -> p b (f b) -> s -> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(a -> b) -> p b (f b) -> p a (f a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f)
  {-# INLINE fmap #-}
instance Semigroup i => Apply (ReifiedIndexedGetter i s) where
  IndexedGetter IndexedGetter i s (a -> b)
mf <.> :: forall a b.
ReifiedIndexedGetter i s (a -> b)
-> ReifiedIndexedGetter i s a -> ReifiedIndexedGetter i s b
<.> IndexedGetter IndexedGetter i s a
ma = IndexedGetter i s b -> ReifiedIndexedGetter i s b
forall i s a. IndexedGetter i s a -> ReifiedIndexedGetter i s a
IndexedGetter (IndexedGetter i s b -> ReifiedIndexedGetter i s b)
-> IndexedGetter i s b -> ReifiedIndexedGetter i s b
forall a b. (a -> b) -> a -> b
$ \p b (f b)
k s
s ->
    case IndexedGetting i (i, a -> b) s (a -> b) -> s -> (i, a -> b)
forall s (m :: * -> *) i a.
MonadReader s m =>
IndexedGetting i (i, a) s a -> m (i, a)
iview IndexedGetting i (i, a -> b) s (a -> b)
IndexedGetter i s (a -> b)
mf s
s of
      (i
i, a -> b
f) -> case IndexedGetting i (i, a) s a -> s -> (i, a)
forall s (m :: * -> *) i a.
MonadReader s m =>
IndexedGetting i (i, a) s a -> m (i, a)
iview IndexedGetting i (i, a) s a
IndexedGetter i s a
ma s
s of
        (i
j, a
a) -> f b -> f s
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f b -> f s) -> f b -> f s
forall a b. (a -> b) -> a -> b
$ p b (f b) -> i -> b -> f b
forall a b. p a b -> i -> a -> b
forall i (p :: * -> * -> *) a b.
Indexable i p =>
p a b -> i -> a -> b
indexed p b (f b)
k (i
i i -> i -> i
forall a. Semigroup a => a -> a -> a
<> i
j) (a -> b
f a
a)
  {-# INLINE (<.>) #-}
newtype ReifiedFold s a = Fold { forall s a. ReifiedFold s a -> Fold s a
runFold :: Fold s a }
instance Profunctor ReifiedFold where
  dimap :: forall a b c d.
(a -> b) -> (c -> d) -> ReifiedFold b c -> ReifiedFold a d
dimap a -> b
f c -> d
g ReifiedFold b c
l = Fold a d -> ReifiedFold a d
forall s a. Fold s a -> ReifiedFold s a
Fold ((a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f ((b -> f b) -> a -> f a)
-> ((d -> f d) -> b -> f b) -> (d -> f d) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedFold b c -> Fold b c
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold b c
l ((c -> f c) -> b -> f b)
-> ((d -> f d) -> c -> f c) -> (d -> f d) -> b -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (c -> d) -> (d -> f d) -> c -> f c
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to c -> d
g)
  {-# INLINE dimap #-}
  rmap :: forall b c a. (b -> c) -> ReifiedFold a b -> ReifiedFold a c
rmap b -> c
g ReifiedFold a b
l = Fold a c -> ReifiedFold a c
forall s a. Fold s a -> ReifiedFold s a
Fold (ReifiedFold a b -> Fold a b
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold a b
l ((b -> f b) -> a -> f a)
-> ((c -> f c) -> b -> f b) -> (c -> f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> c) -> (c -> f c) -> b -> f b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to b -> c
g)
  {-# INLINE rmap #-}
  lmap :: forall a b c. (a -> b) -> ReifiedFold b c -> ReifiedFold a c
lmap a -> b
f ReifiedFold b c
l = Fold a c -> ReifiedFold a c
forall s a. Fold s a -> ReifiedFold s a
Fold ((a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f ((b -> f b) -> a -> f a)
-> ((c -> f c) -> b -> f b) -> (c -> f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedFold b c -> Fold b c
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold b c
l)
  {-# INLINE lmap #-}
instance Sieve ReifiedFold [] where
  sieve :: forall a b. ReifiedFold a b -> a -> [b]
sieve (Fold Fold a b
l) = Getting (Endo [b]) a b -> a -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) a b
Fold a b
l
instance Representable ReifiedFold where
  type Rep ReifiedFold = []
  tabulate :: forall d c. (d -> Rep ReifiedFold c) -> ReifiedFold d c
tabulate d -> Rep ReifiedFold c
f = Fold d c -> ReifiedFold d c
forall s a. Fold s a -> ReifiedFold s a
Fold ((d -> [c]) -> Fold d c
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding d -> [c]
d -> Rep ReifiedFold c
f)
instance Strong ReifiedFold where
  first' :: forall a b c. ReifiedFold a b -> ReifiedFold (a, c) (b, c)
first' ReifiedFold a b
l = Fold (a, c) (b, c) -> ReifiedFold (a, c) (b, c)
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold (a, c) (b, c) -> ReifiedFold (a, c) (b, c))
-> Fold (a, c) (b, c) -> ReifiedFold (a, c) (b, c)
forall a b. (a -> b) -> a -> b
$ \(b, c) -> f (b, c)
f (a
s,c
c) ->
    f a -> f (a, c)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (a, c)) -> f a -> f (a, c)
forall a b. (a -> b) -> a -> b
$ ReifiedFold a b -> Fold a b
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold a b
l ((b -> (b, c))
-> (f (b, c) -> f b) -> ((b, c) -> f (b, c)) -> b -> f b
forall a b c d. (a -> b) -> (c -> d) -> (b -> c) -> a -> d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((b -> c -> (b, c)) -> c -> b -> (b, c)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) c
c) f (b, c) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (b, c) -> f (b, c)
f) a
s
  {-# INLINE first' #-}
  second' :: forall a b c. ReifiedFold a b -> ReifiedFold (c, a) (c, b)
second' ReifiedFold a b
l = Fold (c, a) (c, b) -> ReifiedFold (c, a) (c, b)
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold (c, a) (c, b) -> ReifiedFold (c, a) (c, b))
-> Fold (c, a) (c, b) -> ReifiedFold (c, a) (c, b)
forall a b. (a -> b) -> a -> b
$ \(c, b) -> f (c, b)
f (c
c,a
s) ->
    f a -> f (c, a)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (c, a)) -> f a -> f (c, a)
forall a b. (a -> b) -> a -> b
$ ReifiedFold a b -> Fold a b
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold a b
l ((b -> (c, b))
-> (f (c, b) -> f b) -> ((c, b) -> f (c, b)) -> b -> f b
forall a b c d. (a -> b) -> (c -> d) -> (b -> c) -> a -> d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((,) c
c) f (c, b) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (c, b) -> f (c, b)
f) a
s
  {-# INLINE second' #-}
instance Choice ReifiedFold where
  left' :: forall a b c.
ReifiedFold a b -> ReifiedFold (Either a c) (Either b c)
left' (Fold Fold a b
l) = Fold (Either a c) (Either b c)
-> ReifiedFold (Either a c) (Either b c)
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold (Either a c) (Either b c)
 -> ReifiedFold (Either a c) (Either b c))
-> Fold (Either a c) (Either b c)
-> ReifiedFold (Either a c) (Either b c)
forall a b. (a -> b) -> a -> b
$ (Either a c -> [Either b c]) -> Fold (Either a c) (Either b c)
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((Either a c -> [Either b c]) -> Fold (Either a c) (Either b c))
-> (Either a c -> [Either b c]) -> Fold (Either a c) (Either b c)
forall a b. (a -> b) -> a -> b
$ \Either a c
esc -> case Either a c
esc of
    Left a
s -> b -> Either b c
forall a b. a -> Either a b
Left (b -> Either b c) -> [b] -> [Either b c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Endo [b]) a b -> a -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) a b
Fold a b
l a
s
    Right c
c -> [c -> Either b c
forall a b. b -> Either a b
Right c
c]
  {-# INLINE left' #-}
  right' :: forall a b c.
ReifiedFold a b -> ReifiedFold (Either c a) (Either c b)
right' (Fold Fold a b
l) = Fold (Either c a) (Either c b)
-> ReifiedFold (Either c a) (Either c b)
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold (Either c a) (Either c b)
 -> ReifiedFold (Either c a) (Either c b))
-> Fold (Either c a) (Either c b)
-> ReifiedFold (Either c a) (Either c b)
forall a b. (a -> b) -> a -> b
$ (Either c a -> [Either c b]) -> Fold (Either c a) (Either c b)
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((Either c a -> [Either c b]) -> Fold (Either c a) (Either c b))
-> (Either c a -> [Either c b]) -> Fold (Either c a) (Either c b)
forall a b. (a -> b) -> a -> b
$ \Either c a
ecs -> case Either c a
ecs of
    Left c
c -> [c -> Either c b
forall a b. a -> Either a b
Left c
c]
    Right a
s -> b -> Either c b
forall a b. b -> Either a b
Right (b -> Either c b) -> [b] -> [Either c b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Endo [b]) a b -> a -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) a b
Fold a b
l a
s
  {-# INLINE right' #-}
instance Cat.Category ReifiedFold where
  id :: forall a. ReifiedFold a a
id = Fold a a -> ReifiedFold a a
forall s a. Fold s a -> ReifiedFold s a
Fold (a -> f a) -> a -> f a
forall a. a -> a
Fold a a
id
  ReifiedFold b c
l . :: forall b c a. ReifiedFold b c -> ReifiedFold a b -> ReifiedFold a c
. ReifiedFold a b
r = Fold a c -> ReifiedFold a c
forall s a. Fold s a -> ReifiedFold s a
Fold (ReifiedFold a b -> Fold a b
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold a b
r ((b -> f b) -> a -> f a)
-> ((c -> f c) -> b -> f b) -> (c -> f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedFold b c -> Fold b c
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold b c
l)
  {-# INLINE (.) #-}
instance Arrow ReifiedFold where
  arr :: forall b c. (b -> c) -> ReifiedFold b c
arr b -> c
f = Fold b c -> ReifiedFold b c
forall s a. Fold s a -> ReifiedFold s a
Fold ((b -> c) -> (c -> f c) -> b -> f b
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to b -> c
f)
  {-# INLINE arr #-}
  first :: forall a b c. ReifiedFold a b -> ReifiedFold (a, c) (b, c)
first = ReifiedFold b c -> ReifiedFold (b, d) (c, d)
forall a b c. ReifiedFold a b -> ReifiedFold (a, c) (b, c)
forall (p :: * -> * -> *) a b c.
Strong p =>
p a b -> p (a, c) (b, c)
first'
  {-# INLINE first #-}
  second :: forall a b c. ReifiedFold a b -> ReifiedFold (c, a) (c, b)
second = ReifiedFold b c -> ReifiedFold (d, b) (d, c)
forall a b c. ReifiedFold a b -> ReifiedFold (c, a) (c, b)
forall (p :: * -> * -> *) a b c.
Strong p =>
p a b -> p (c, a) (c, b)
second'
  {-# INLINE second #-}
  Fold Fold b c
l *** :: forall b c b' c'.
ReifiedFold b c -> ReifiedFold b' c' -> ReifiedFold (b, b') (c, c')
*** Fold Fold b' c'
r = Fold (b, b') (c, c') -> ReifiedFold (b, b') (c, c')
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold (b, b') (c, c') -> ReifiedFold (b, b') (c, c'))
-> Fold (b, b') (c, c') -> ReifiedFold (b, b') (c, c')
forall a b. (a -> b) -> a -> b
$ ((b, b') -> [(c, c')]) -> Fold (b, b') (c, c')
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding (((b, b') -> [(c, c')]) -> Fold (b, b') (c, c'))
-> ((b, b') -> [(c, c')]) -> Fold (b, b') (c, c')
forall a b. (a -> b) -> a -> b
$ \(b
x,b'
y) -> (,) (c -> c' -> (c, c')) -> [c] -> [c' -> (c, c')]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Endo [c]) b c -> b -> [c]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [c]) b c
Fold b c
l b
x [c' -> (c, c')] -> [c'] -> [(c, c')]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Getting (Endo [c']) b' c' -> b' -> [c']
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [c']) b' c'
Fold b' c'
r b'
y
  {-# INLINE (***) #-}
  Fold Fold b c
l &&& :: forall b c c'.
ReifiedFold b c -> ReifiedFold b c' -> ReifiedFold b (c, c')
&&& Fold Fold b c'
r = Fold b (c, c') -> ReifiedFold b (c, c')
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold b (c, c') -> ReifiedFold b (c, c'))
-> Fold b (c, c') -> ReifiedFold b (c, c')
forall a b. (a -> b) -> a -> b
$ (b -> [(c, c')]) -> Fold b (c, c')
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((b -> [(c, c')]) -> Fold b (c, c'))
-> (b -> [(c, c')]) -> Fold b (c, c')
forall a b. (a -> b) -> a -> b
$ \b
x -> (,) (c -> c' -> (c, c')) -> [c] -> [c' -> (c, c')]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Endo [c]) b c -> b -> [c]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [c]) b c
Fold b c
l b
x [c' -> (c, c')] -> [c'] -> [(c, c')]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Getting (Endo [c']) b c' -> b -> [c']
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [c']) b c'
Fold b c'
r b
x
  {-# INLINE (&&&) #-}
instance ArrowChoice ReifiedFold where
  left :: forall a b c.
ReifiedFold a b -> ReifiedFold (Either a c) (Either b c)
left = ReifiedFold b c -> ReifiedFold (Either b d) (Either c d)
forall a b c.
ReifiedFold a b -> ReifiedFold (Either a c) (Either b c)
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either a c) (Either b c)
left'
  {-# INLINE left #-}
  right :: forall a b c.
ReifiedFold a b -> ReifiedFold (Either c a) (Either c b)
right = ReifiedFold b c -> ReifiedFold (Either d b) (Either d c)
forall a b c.
ReifiedFold a b -> ReifiedFold (Either c a) (Either c b)
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right'
  {-# INLINE right #-}
instance ArrowApply ReifiedFold where
  app :: forall b c. ReifiedFold (ReifiedFold b c, b) c
app = Fold (ReifiedFold b c, b) c -> ReifiedFold (ReifiedFold b c, b) c
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold (ReifiedFold b c, b) c -> ReifiedFold (ReifiedFold b c, b) c)
-> Fold (ReifiedFold b c, b) c
-> ReifiedFold (ReifiedFold b c, b) c
forall a b. (a -> b) -> a -> b
$ ((ReifiedFold b c, b) -> [c]) -> Fold (ReifiedFold b c, b) c
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding (((ReifiedFold b c, b) -> [c]) -> Fold (ReifiedFold b c, b) c)
-> ((ReifiedFold b c, b) -> [c]) -> Fold (ReifiedFold b c, b) c
forall a b. (a -> b) -> a -> b
$ \(Fold Fold b c
bc, b
b) -> Getting (Endo [c]) b c -> b -> [c]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [c]) b c
Fold b c
bc b
b
  {-# INLINE app #-}
instance Functor (ReifiedFold s) where
  fmap :: forall a b. (a -> b) -> ReifiedFold s a -> ReifiedFold s b
fmap a -> b
f ReifiedFold s a
l = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (ReifiedFold s a -> Fold s a
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold s a
l((a -> f a) -> s -> f s)
-> ((b -> f b) -> a -> f a) -> (b -> f b) -> s -> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f)
  {-# INLINE fmap #-}
instance Apply (ReifiedFold s) where
  Fold Fold s (a -> b)
mf <.> :: forall a b.
ReifiedFold s (a -> b) -> ReifiedFold s a -> ReifiedFold s b
<.> Fold Fold s a
ma = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s b -> ReifiedFold s b) -> Fold s b -> ReifiedFold s b
forall a b. (a -> b) -> a -> b
$ (s -> [b]) -> Fold s b
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [b]) -> Fold s b) -> (s -> [b]) -> Fold s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a -> b]) s (a -> b) -> s -> [a -> b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a -> b]) s (a -> b)
Fold s (a -> b)
mf s
s [a -> b] -> [a] -> [b]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
ma s
s
  {-# INLINE (<.>) #-}
  Fold Fold s a
mf <. :: forall a b. ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s a
<. Fold Fold s b
ma = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s a -> ReifiedFold s a) -> Fold s a -> ReifiedFold s a
forall a b. (a -> b) -> a -> b
$ (s -> [a]) -> Fold s a
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [a]) -> Fold s a) -> (s -> [a]) -> Fold s a
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
mf s
s [a] -> [b] -> [a]
forall a b. [a] -> [b] -> [a]
forall (f :: * -> *) a b. Apply f => f a -> f b -> f a
<. Getting (Endo [b]) s b -> s -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) s b
Fold s b
ma s
s
  {-# INLINE (<.) #-}
  Fold Fold s a
mf .> :: forall a b. ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b
.> Fold Fold s b
ma = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s b -> ReifiedFold s b) -> Fold s b -> ReifiedFold s b
forall a b. (a -> b) -> a -> b
$ (s -> [b]) -> Fold s b
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [b]) -> Fold s b) -> (s -> [b]) -> Fold s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
mf s
s [a] -> [b] -> [b]
forall a b. [a] -> [b] -> [b]
forall (f :: * -> *) a b. Apply f => f a -> f b -> f b
.> Getting (Endo [b]) s b -> s -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) s b
Fold s b
ma s
s
  {-# INLINE (.>) #-}
instance Applicative (ReifiedFold s) where
  pure :: forall a. a -> ReifiedFold s a
pure a
a = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s a -> ReifiedFold s a) -> Fold s a -> ReifiedFold s a
forall a b. (a -> b) -> a -> b
$ (s -> [a]) -> Fold s a
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [a]) -> Fold s a) -> (s -> [a]) -> Fold s a
forall a b. (a -> b) -> a -> b
$ \s
_ -> [a
a]
  {-# INLINE pure #-}
  Fold Fold s (a -> b)
mf <*> :: forall a b.
ReifiedFold s (a -> b) -> ReifiedFold s a -> ReifiedFold s b
<*> Fold Fold s a
ma = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s b -> ReifiedFold s b) -> Fold s b -> ReifiedFold s b
forall a b. (a -> b) -> a -> b
$ (s -> [b]) -> Fold s b
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [b]) -> Fold s b) -> (s -> [b]) -> Fold s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a -> b]) s (a -> b) -> s -> [a -> b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a -> b]) s (a -> b)
Fold s (a -> b)
mf s
s [a -> b] -> [a] -> [b]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
ma s
s
  {-# INLINE (<*>) #-}
  Fold Fold s a
mf <* :: forall a b. ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s a
<* Fold Fold s b
ma = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s a -> ReifiedFold s a) -> Fold s a -> ReifiedFold s a
forall a b. (a -> b) -> a -> b
$ (s -> [a]) -> Fold s a
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [a]) -> Fold s a) -> (s -> [a]) -> Fold s a
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
mf s
s [a] -> [b] -> [a]
forall a b. [a] -> [b] -> [a]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Getting (Endo [b]) s b -> s -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) s b
Fold s b
ma s
s
  {-# INLINE (<*) #-}
  Fold Fold s a
mf *> :: forall a b. ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b
*> Fold Fold s b
ma = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s b -> ReifiedFold s b) -> Fold s b -> ReifiedFold s b
forall a b. (a -> b) -> a -> b
$ (s -> [b]) -> Fold s b
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [b]) -> Fold s b) -> (s -> [b]) -> Fold s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
mf s
s [a] -> [b] -> [b]
forall a b. [a] -> [b] -> [b]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Getting (Endo [b]) s b -> s -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [b]) s b
Fold s b
ma s
s
  {-# INLINE (*>) #-}
instance Alternative (ReifiedFold s) where
  empty :: forall a. ReifiedFold s a
empty = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (a -> f a) -> s -> f s
Fold s a
forall (f :: * -> *) pafb s. Applicative f => pafb -> s -> f s
ignored
  {-# INLINE empty #-}
  Fold Fold s a
ma <|> :: forall a. ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
<|> Fold Fold s a
mb = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s a -> ReifiedFold s a) -> Fold s a -> ReifiedFold s a
forall a b. (a -> b) -> a -> b
$ (s -> [a]) -> Fold s a
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding (\s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
ma s
s [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
mb s
s)
  {-# INLINE (<|>) #-}
instance Bind (ReifiedFold s) where
  Fold Fold s a
ma >>- :: forall a b.
ReifiedFold s a -> (a -> ReifiedFold s b) -> ReifiedFold s b
>>- a -> ReifiedFold s b
f = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s b -> ReifiedFold s b) -> Fold s b -> ReifiedFold s b
forall a b. (a -> b) -> a -> b
$ (s -> [b]) -> Fold s b
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [b]) -> Fold s b) -> (s -> [b]) -> Fold s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
ma s
s [a] -> (a -> [b]) -> [b]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Bind m => m a -> (a -> m b) -> m b
>>- \a
a -> Getting (Endo [b]) s b -> s -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf (ReifiedFold s b -> Fold s b
forall s a. ReifiedFold s a -> Fold s a
runFold (a -> ReifiedFold s b
f a
a)) s
s
  {-# INLINE (>>-) #-}
instance Monad (ReifiedFold s) where
  return :: forall a. a -> ReifiedFold s a
return = a -> ReifiedFold s a
forall a. a -> ReifiedFold s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  Fold Fold s a
ma >>= :: forall a b.
ReifiedFold s a -> (a -> ReifiedFold s b) -> ReifiedFold s b
>>= a -> ReifiedFold s b
f = Fold s b -> ReifiedFold s b
forall s a. Fold s a -> ReifiedFold s a
Fold (Fold s b -> ReifiedFold s b) -> Fold s b -> ReifiedFold s b
forall a b. (a -> b) -> a -> b
$ (s -> [b]) -> Fold s b
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding ((s -> [b]) -> Fold s b) -> (s -> [b]) -> Fold s b
forall a b. (a -> b) -> a -> b
$ \s
s -> Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
ma s
s [a] -> (a -> [b]) -> [b]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a -> Getting (Endo [b]) s b -> s -> [b]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf (ReifiedFold s b -> Fold s b
forall s a. ReifiedFold s a -> Fold s a
runFold (a -> ReifiedFold s b
f a
a)) s
s
  {-# INLINE (>>=) #-}
instance MonadPlus (ReifiedFold s) where
  mzero :: forall a. ReifiedFold s a
mzero = ReifiedFold s a
forall a. ReifiedFold s a
forall (f :: * -> *) a. Alternative f => f a
empty
  {-# INLINE mzero #-}
  mplus :: forall a. ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
mplus = ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
forall a. ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
  {-# INLINE mplus #-}
instance MonadReader s (ReifiedFold s) where
  ask :: ReifiedFold s s
ask = Fold s s -> ReifiedFold s s
forall s a. Fold s a -> ReifiedFold s a
Fold (s -> f s) -> s -> f s
forall a. a -> a
Fold s s
id
  {-# INLINE ask #-}
  local :: forall a. (s -> s) -> ReifiedFold s a -> ReifiedFold s a
local s -> s
f ReifiedFold s a
m = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold ((s -> s) -> (s -> f s) -> s -> f s
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to s -> s
f ((s -> f s) -> s -> f s)
-> ((a -> f a) -> s -> f s) -> (a -> f a) -> s -> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedFold s a -> Fold s a
forall s a. ReifiedFold s a -> Fold s a
runFold ReifiedFold s a
m)
  {-# INLINE local #-}
instance Semigroup (ReifiedFold s a) where
  <> :: ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
(<>) = ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
forall a. ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
  {-# INLINE (<>) #-}
instance Monoid (ReifiedFold s a) where
  mempty :: ReifiedFold s a
mempty = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (a -> f a) -> s -> f s
Fold s a
forall (f :: * -> *) pafb s. Applicative f => pafb -> s -> f s
ignored
  {-# INLINE mempty #-}
#if !(MIN_VERSION_base(4,11,0))
  mappend = (<|>)
  {-# INLINE mappend #-}
#endif
instance Alt (ReifiedFold s) where
  <!> :: forall a. ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
(<!>) = ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
forall a. ReifiedFold s a -> ReifiedFold s a -> ReifiedFold s a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
  {-# INLINE (<!>) #-}
instance Plus (ReifiedFold s) where
  zero :: forall a. ReifiedFold s a
zero = Fold s a -> ReifiedFold s a
forall s a. Fold s a -> ReifiedFold s a
Fold (a -> f a) -> s -> f s
Fold s a
forall (f :: * -> *) pafb s. Applicative f => pafb -> s -> f s
ignored
  {-# INLINE zero #-}
newtype ReifiedIndexedFold i s a = IndexedFold { forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold :: IndexedFold i s a }
instance Semigroup (ReifiedIndexedFold i s a) where
  <> :: ReifiedIndexedFold i s a
-> ReifiedIndexedFold i s a -> ReifiedIndexedFold i s a
(<>) = ReifiedIndexedFold i s a
-> ReifiedIndexedFold i s a -> ReifiedIndexedFold i s a
forall a.
ReifiedIndexedFold i s a
-> ReifiedIndexedFold i s a -> ReifiedIndexedFold i s a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
(<!>)
  {-# INLINE (<>) #-}
instance Monoid (ReifiedIndexedFold i s a) where
  mempty :: ReifiedIndexedFold i s a
mempty = IndexedFold i s a -> ReifiedIndexedFold i s a
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold p a (f a) -> s -> f s
forall (f :: * -> *) pafb s. Applicative f => pafb -> s -> f s
IndexedFold i s a
ignored
  {-# INLINE mempty #-}
#if !(MIN_VERSION_base(4,11,0))
  mappend = (<!>)
  {-# INLINE mappend #-}
#endif
instance Alt (ReifiedIndexedFold i s) where
  IndexedFold IndexedFold i s a
ma <!> :: forall a.
ReifiedIndexedFold i s a
-> ReifiedIndexedFold i s a -> ReifiedIndexedFold i s a
<!> IndexedFold IndexedFold i s a
mb = IndexedFold i s a -> ReifiedIndexedFold i s a
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold (IndexedFold i s a -> ReifiedIndexedFold i s a)
-> IndexedFold i s a -> ReifiedIndexedFold i s a
forall a b. (a -> b) -> a -> b
$
    (s -> [(i, a)]) -> Over p f s s a a
forall (f :: * -> *) i (p :: * -> * -> *) (g :: * -> *) s a t b.
(Foldable f, Indexable i p, Contravariant g, Applicative g) =>
(s -> f (i, a)) -> Over p g s t a b
ifolding ((s -> [(i, a)]) -> Over p f s s a a)
-> (s -> [(i, a)]) -> Over p f s s a a
forall a b. (a -> b) -> a -> b
$ \s
s -> IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
forall i a s. IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
itoListOf IndexedGetting i (Endo [(i, a)]) s a
IndexedFold i s a
ma s
s [(i, a)] -> [(i, a)] -> [(i, a)]
forall a. [a] -> [a] -> [a]
++ IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
forall i a s. IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
itoListOf IndexedGetting i (Endo [(i, a)]) s a
IndexedFold i s a
mb s
s
  {-# INLINE (<!>) #-}
instance Plus (ReifiedIndexedFold i s) where
  zero :: forall a. ReifiedIndexedFold i s a
zero = IndexedFold i s a -> ReifiedIndexedFold i s a
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold p a (f a) -> s -> f s
forall (f :: * -> *) pafb s. Applicative f => pafb -> s -> f s
IndexedFold i s a
ignored
  {-# INLINE zero #-}
instance Functor (ReifiedIndexedFold i s) where
  fmap :: forall a b.
(a -> b) -> ReifiedIndexedFold i s a -> ReifiedIndexedFold i s b
fmap a -> b
f ReifiedIndexedFold i s a
l = IndexedFold i s b -> ReifiedIndexedFold i s b
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold (ReifiedIndexedFold i s a -> IndexedFold i s a
forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold ReifiedIndexedFold i s a
l (p a (f a) -> s -> f s)
-> (p b (f b) -> p a (f a)) -> p b (f b) -> s -> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> p b (f b) -> p a (f a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f)
  {-# INLINE fmap #-}
instance Profunctor (ReifiedIndexedFold i) where
  dimap :: forall a b c d.
(a -> b)
-> (c -> d) -> ReifiedIndexedFold i b c -> ReifiedIndexedFold i a d
dimap a -> b
f c -> d
g ReifiedIndexedFold i b c
l = IndexedFold i a d -> ReifiedIndexedFold i a d
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold ((a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f ((b -> f b) -> a -> f a)
-> (p d (f d) -> b -> f b) -> p d (f d) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedIndexedFold i b c -> IndexedFold i b c
forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold ReifiedIndexedFold i b c
l (p c (f c) -> b -> f b)
-> (p d (f d) -> p c (f c)) -> p d (f d) -> b -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (c -> d) -> p d (f d) -> p c (f c)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to c -> d
g)
  {-# INLINE dimap #-}
  lmap :: forall a b c.
(a -> b) -> ReifiedIndexedFold i b c -> ReifiedIndexedFold i a c
lmap a -> b
f ReifiedIndexedFold i b c
l = IndexedFold i a c -> ReifiedIndexedFold i a c
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold ((a -> b) -> (b -> f b) -> a -> f a
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to a -> b
f ((b -> f b) -> a -> f a)
-> (p c (f c) -> b -> f b) -> p c (f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReifiedIndexedFold i b c -> IndexedFold i b c
forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold ReifiedIndexedFold i b c
l)
  {-# INLINE lmap #-}
  rmap :: forall b c a.
(b -> c) -> ReifiedIndexedFold i a b -> ReifiedIndexedFold i a c
rmap b -> c
g ReifiedIndexedFold i a b
l = IndexedFold i a c -> ReifiedIndexedFold i a c
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold (ReifiedIndexedFold i a b -> IndexedFold i a b
forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold ReifiedIndexedFold i a b
l (p b (f b) -> a -> f a)
-> (p c (f c) -> p b (f b)) -> p c (f c) -> a -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> c) -> p c (f c) -> p b (f b)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to b -> c
g)
  {-# INLINE rmap #-}
instance Sieve (ReifiedIndexedFold i) (Compose [] ((,) i)) where
  sieve :: forall a b. ReifiedIndexedFold i a b -> a -> Compose [] ((,) i) b
sieve (IndexedFold IndexedFold i a b
l) = [(i, b)] -> Compose [] ((,) i) b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose ([(i, b)] -> Compose [] ((,) i) b)
-> (a -> [(i, b)]) -> a -> Compose [] ((,) i) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndexedGetting i (Endo [(i, b)]) a b -> a -> [(i, b)]
forall i a s. IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
itoListOf IndexedGetting i (Endo [(i, b)]) a b
IndexedFold i a b
l
  {-# INLINE sieve #-}
instance Representable (ReifiedIndexedFold i) where
  type Rep (ReifiedIndexedFold i) = Compose [] ((,) i)
  tabulate :: forall d c.
(d -> Rep (ReifiedIndexedFold i) c) -> ReifiedIndexedFold i d c
tabulate d -> Rep (ReifiedIndexedFold i) c
k = IndexedFold i d c -> ReifiedIndexedFold i d c
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold (IndexedFold i d c -> ReifiedIndexedFold i d c)
-> IndexedFold i d c -> ReifiedIndexedFold i d c
forall a b. (a -> b) -> a -> b
$ \p c (f c)
f -> f () -> f d
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f () -> f d) -> (d -> f ()) -> d -> f d
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((i, c) -> f Any) -> [(i, c)] -> f ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (f c -> f Any
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f c -> f Any) -> ((i, c) -> f c) -> (i, c) -> f Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> c -> f c) -> (i, c) -> f c
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (p c (f c) -> i -> c -> f c
forall a b. p a b -> i -> a -> b
forall i (p :: * -> * -> *) a b.
Indexable i p =>
p a b -> i -> a -> b
indexed p c (f c)
f)) ([(i, c)] -> f ()) -> (d -> [(i, c)]) -> d -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose [] ((,) i) c -> [(i, c)]
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose (Compose [] ((,) i) c -> [(i, c)])
-> (d -> Compose [] ((,) i) c) -> d -> [(i, c)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Compose [] ((,) i) c
d -> Rep (ReifiedIndexedFold i) c
k
  {-# INLINE tabulate #-}
instance Strong (ReifiedIndexedFold i) where
  first' :: forall a b c.
ReifiedIndexedFold i a b -> ReifiedIndexedFold i (a, c) (b, c)
first' ReifiedIndexedFold i a b
l  = IndexedFold i (a, c) (b, c) -> ReifiedIndexedFold i (a, c) (b, c)
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold (IndexedFold i (a, c) (b, c) -> ReifiedIndexedFold i (a, c) (b, c))
-> IndexedFold i (a, c) (b, c)
-> ReifiedIndexedFold i (a, c) (b, c)
forall a b. (a -> b) -> a -> b
$ \p (b, c) (f (b, c))
f (a
s,c
c) ->
    f a -> f (a, c)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (a, c)) -> f a -> f (a, c)
forall a b. (a -> b) -> a -> b
$ ReifiedIndexedFold i a b -> IndexedFold i a b
forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold ReifiedIndexedFold i a b
l ((b -> (b, c))
-> (f (b, c) -> f b) -> p (b, c) (f (b, c)) -> p b (f b)
forall a b c d. (a -> b) -> (c -> d) -> p b c -> p a d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((b -> c -> (b, c)) -> c -> b -> (b, c)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) c
c) f (b, c) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom p (b, c) (f (b, c))
f) a
s
  {-# INLINE first' #-}
  second' :: forall a b c.
ReifiedIndexedFold i a b -> ReifiedIndexedFold i (c, a) (c, b)
second' ReifiedIndexedFold i a b
l = IndexedFold i (c, a) (c, b) -> ReifiedIndexedFold i (c, a) (c, b)
forall i s a. IndexedFold i s a -> ReifiedIndexedFold i s a
IndexedFold (IndexedFold i (c, a) (c, b) -> ReifiedIndexedFold i (c, a) (c, b))
-> IndexedFold i (c, a) (c, b)
-> ReifiedIndexedFold i (c, a) (c, b)
forall a b. (a -> b) -> a -> b
$ \p (c, b) (f (c, b))
f (c
c,a
s) ->
    f a -> f (c, a)
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom (f a -> f (c, a)) -> f a -> f (c, a)
forall a b. (a -> b) -> a -> b
$ ReifiedIndexedFold i a b -> IndexedFold i a b
forall i s a. ReifiedIndexedFold i s a -> IndexedFold i s a
runIndexedFold ReifiedIndexedFold i a b
l ((b -> (c, b))
-> (f (c, b) -> f b) -> p (c, b) (f (c, b)) -> p b (f b)
forall a b c d. (a -> b) -> (c -> d) -> p b c -> p a d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap ((,) c
c) f (c, b) -> f b
forall (f :: * -> *) a b.
(Functor f, Contravariant f) =>
f a -> f b
phantom p (c, b) (f (c, b))
f) a
s
  {-# INLINE second' #-}
newtype ReifiedSetter s t a b = Setter { forall s t a b. ReifiedSetter s t a b -> Setter s t a b
runSetter :: Setter s t a b }
type ReifiedSetter' s a = ReifiedSetter s s a a
newtype ReifiedIndexedSetter i s t a b =
  IndexedSetter { forall i s t a b.
ReifiedIndexedSetter i s t a b -> IndexedSetter i s t a b
runIndexedSetter :: IndexedSetter i s t a b }
type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a
newtype ReifiedIso s t a b = Iso { forall s t a b. ReifiedIso s t a b -> Iso s t a b
runIso :: Iso s t a b }
type ReifiedIso' s a = ReifiedIso s s a a
newtype ReifiedPrism s t a b = Prism { forall s t a b. ReifiedPrism s t a b -> Prism s t a b
runPrism :: Prism s t a b }
type ReifiedPrism' s a = ReifiedPrism s s a a