lens-4.16: Lenses, Folds and Traversals

Copyright(C) 2012-2016 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell98

Control.Lens.Internal.Indexed

Contents

Description

Internal implementation details for Indexed lens-likes

Synopsis

An Indexed Profunctor

newtype Indexed i a b Source #

A function with access to a index. This constructor may be useful when you need to store an Indexable in a container to avoid ImpredicativeTypes.

index :: Indexed i a b -> i -> a -> b

Constructors

Indexed 

Fields

Instances

(~) * i j => Indexable i (Indexed j) Source # 

Methods

indexed :: Indexed j a b -> i -> a -> b Source #

Arrow (Indexed i) Source # 

Methods

arr :: (b -> c) -> Indexed i b c #

first :: Indexed i b c -> Indexed i (b, d) (c, d) #

second :: Indexed i b c -> Indexed i (d, b) (d, c) #

(***) :: Indexed i b c -> Indexed i b' c' -> Indexed i (b, b') (c, c') #

(&&&) :: Indexed i b c -> Indexed i b c' -> Indexed i b (c, c') #

ArrowChoice (Indexed i) Source # 

Methods

left :: Indexed i b c -> Indexed i (Either b d) (Either c d) #

right :: Indexed i b c -> Indexed i (Either d b) (Either d c) #

(+++) :: Indexed i b c -> Indexed i b' c' -> Indexed i (Either b b') (Either c c') #

(|||) :: Indexed i b d -> Indexed i c d -> Indexed i (Either b c) d #

ArrowApply (Indexed i) Source # 

Methods

app :: Indexed i (Indexed i b c, b) c #

ArrowLoop (Indexed i) Source # 

Methods

loop :: Indexed i (b, d) (c, d) -> Indexed i b c #

Representable (Indexed i) Source # 

Associated Types

type Rep (Indexed i :: * -> * -> *) :: * -> * #

Methods

tabulate :: (d -> Rep (Indexed i) c) -> Indexed i d c #

Corepresentable (Indexed i) Source # 

Associated Types

type Corep (Indexed i :: * -> * -> *) :: * -> * #

Methods

cotabulate :: (Corep (Indexed i) d -> c) -> Indexed i d c #

Choice (Indexed i) Source # 

Methods

left' :: Indexed i a b -> Indexed i (Either a c) (Either b c) #

right' :: Indexed i a b -> Indexed i (Either c a) (Either c b) #

Closed (Indexed i) Source # 

Methods

closed :: Indexed i a b -> Indexed i (x -> a) (x -> b) #

Strong (Indexed i) Source # 

Methods

first' :: Indexed i a b -> Indexed i (a, c) (b, c) #

second' :: Indexed i a b -> Indexed i (c, a) (c, b) #

Costrong (Indexed i) Source # 

Methods

unfirst :: Indexed i (a, d) (b, d) -> Indexed i a b #

unsecond :: Indexed i (d, a) (d, b) -> Indexed i a b #

Profunctor (Indexed i) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Indexed i b c -> Indexed i a d #

lmap :: (a -> b) -> Indexed i b c -> Indexed i a c #

rmap :: (b -> c) -> Indexed i a b -> Indexed i a c #

(#.) :: Coercible * c b => (b -> c) -> Indexed i a b -> Indexed i a c #

(.#) :: Coercible * b a => Indexed i b c -> (a -> b) -> Indexed i a c #

Conjoined (Indexed i) Source # 

Methods

distrib :: Functor f => Indexed i a b -> Indexed i (f a) (f b) Source #

conjoined :: (((* -> * -> *) ~ Indexed i) (LiftedRep -> LiftedRep) -> q (a -> b) r) -> q (Indexed i a b) r -> q (Indexed i a b) r Source #

Bizarre (Indexed Int) Mafic Source # 

Methods

bazaar :: Applicative f => Indexed Int a (f b) -> Mafic a b t -> f t Source #

Category * (Indexed i) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Cosieve (Indexed i) ((,) i) Source # 

Methods

cosieve :: Indexed i a b -> (i, a) -> b #

Sellable (Indexed i) (Molten i) Source # 

Methods

sell :: Indexed i a (Molten i a b b) Source #

Bizarre (Indexed i) (Molten i) Source # 

Methods

bazaar :: Applicative f => Indexed i a (f b) -> Molten i a b t -> f t Source #

Sieve (Indexed i) ((->) LiftedRep LiftedRep i) Source # 

Methods

sieve :: Indexed i a b -> a -> (LiftedRep -> LiftedRep) i b #

Monad (Indexed i a) Source # 

Methods

(>>=) :: Indexed i a a -> (a -> Indexed i a b) -> Indexed i a b #

(>>) :: Indexed i a a -> Indexed i a b -> Indexed i a b #

return :: a -> Indexed i a a #

fail :: String -> Indexed i a a #

Functor (Indexed i a) Source # 

Methods

fmap :: (a -> b) -> Indexed i a a -> Indexed i a b #

(<$) :: a -> Indexed i a b -> Indexed i a a #

MonadFix (Indexed i a) Source # 

Methods

mfix :: (a -> Indexed i a a) -> Indexed i a a #

Applicative (Indexed i a) Source # 

Methods

pure :: a -> Indexed i a a #

(<*>) :: Indexed i a (a -> b) -> Indexed i a a -> Indexed i a b #

liftA2 :: (a -> b -> c) -> Indexed i a a -> Indexed i a b -> Indexed i a c #

(*>) :: Indexed i a a -> Indexed i a b -> Indexed i a b #

(<*) :: Indexed i a a -> Indexed i a b -> Indexed i a a #

Apply (Indexed i a) Source # 

Methods

(<.>) :: Indexed i a (a -> b) -> Indexed i a a -> Indexed i a b #

(.>) :: Indexed i a a -> Indexed i a b -> Indexed i a b #

(<.) :: Indexed i a a -> Indexed i a b -> Indexed i a a #

liftF2 :: (a -> b -> c) -> Indexed i a a -> Indexed i a b -> Indexed i a c #

Bind (Indexed i a) Source # 

Methods

(>>-) :: Indexed i a a -> (a -> Indexed i a b) -> Indexed i a b #

join :: Indexed i a (Indexed i a a) -> Indexed i a a #

type Rep (Indexed i) Source # 
type Rep (Indexed i) = (->) LiftedRep LiftedRep i
type Corep (Indexed i) Source # 
type Corep (Indexed i) = (,) i

Classes

class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined p where Source #

This is a Profunctor that is both Corepresentable by f and Representable by g such that f is left adjoint to g. From this you can derive a lot of structure due to the preservation of limits and colimits.

Methods

distrib :: Functor f => p a b -> p (f a) (f b) Source #

Conjoined is strong enough to let us distribute every Conjoined Profunctor over every Haskell Functor. This is effectively a generalization of fmap.

conjoined :: (p ~ (->) => q (a -> b) r) -> q (p a b) r -> q (p a b) r Source #

This permits us to make a decision at an outermost point about whether or not we use an index.

Ideally any use of this function should be done in such a way so that you compute the same answer, but this cannot be enforced at the type level.

Instances

Conjoined ReifiedGetter Source # 

Methods

distrib :: Functor f => ReifiedGetter a b -> ReifiedGetter (f a) (f b) Source #

conjoined :: (((* -> * -> *) ~ ReifiedGetter) (LiftedRep -> LiftedRep) -> q (a -> b) r) -> q (ReifiedGetter a b) r -> q (ReifiedGetter a b) r Source #

Conjoined (Indexed i) Source # 

Methods

distrib :: Functor f => Indexed i a b -> Indexed i (f a) (f b) Source #

conjoined :: (((* -> * -> *) ~ Indexed i) (LiftedRep -> LiftedRep) -> q (a -> b) r) -> q (Indexed i a b) r -> q (Indexed i a b) r Source #

Conjoined ((->) LiftedRep LiftedRep) Source # 

Methods

distrib :: Functor f => (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) (f a) (f b) Source #

conjoined :: (((* -> * -> *) ~ (LiftedRep -> LiftedRep)) (LiftedRep -> LiftedRep) -> q (a -> b) r) -> q ((LiftedRep -> LiftedRep) a b) r -> q ((LiftedRep -> LiftedRep) a b) r Source #

class Conjoined p => Indexable i p where Source #

This class permits overloading of function application for things that also admit a notion of a key or index.

Minimal complete definition

indexed

Methods

indexed :: p a b -> i -> a -> b Source #

Build a function from an indexed function.

Instances

(~) * i j => Indexable i (Indexed j) Source # 

Methods

indexed :: Indexed j a b -> i -> a -> b Source #

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

Methods

indexed :: (LiftedRep -> LiftedRep) a b -> i -> a -> b Source #

Indexing

newtype Indexing f a Source #

Applicative composition of State Int with a Functor, used by indexed.

Constructors

Indexing 

Fields

Instances

Functor f => Functor (Indexing f) Source # 

Methods

fmap :: (a -> b) -> Indexing f a -> Indexing f b #

(<$) :: a -> Indexing f b -> Indexing f a #

Applicative f => Applicative (Indexing f) Source # 

Methods

pure :: a -> Indexing f a #

(<*>) :: Indexing f (a -> b) -> Indexing f a -> Indexing f b #

liftA2 :: (a -> b -> c) -> Indexing f a -> Indexing f b -> Indexing f c #

(*>) :: Indexing f a -> Indexing f b -> Indexing f b #

(<*) :: Indexing f a -> Indexing f b -> Indexing f a #

Contravariant f => Contravariant (Indexing f) Source # 

Methods

contramap :: (a -> b) -> Indexing f b -> Indexing f a #

(>$) :: b -> Indexing f b -> Indexing f a #

Apply f => Apply (Indexing f) Source # 

Methods

(<.>) :: Indexing f (a -> b) -> Indexing f a -> Indexing f b #

(.>) :: Indexing f a -> Indexing f b -> Indexing f b #

(<.) :: Indexing f a -> Indexing f b -> Indexing f a #

liftF2 :: (a -> b -> c) -> Indexing f a -> Indexing f b -> Indexing f c #

Semigroup (f a) => Semigroup (Indexing f a) Source # 

Methods

(<>) :: Indexing f a -> Indexing f a -> Indexing f a #

sconcat :: NonEmpty (Indexing f a) -> Indexing f a #

stimes :: Integral b => b -> Indexing f a -> Indexing f a #

Monoid (f a) => Monoid (Indexing f a) Source #
>>> "cat" ^@.. (folded <> folded)
[(0,'c'),(1,'a'),(2,'t'),(0,'c'),(1,'a'),(2,'t')]
>>> "cat" ^@.. indexing (folded <> folded)
[(0,'c'),(1,'a'),(2,'t'),(3,'c'),(4,'a'),(5,'t')]

Methods

mempty :: Indexing f a #

mappend :: Indexing f a -> Indexing f a -> Indexing f a #

mconcat :: [Indexing f a] -> Indexing f a #

indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t Source #

Transform a Traversal into an IndexedTraversal or a Fold into an IndexedFold, etc.

indexing :: Traversal s t a b -> IndexedTraversal Int s t a b
indexing :: Prism s t a b     -> IndexedTraversal Int s t a b
indexing :: Lens s t a b      -> IndexedLens Int  s t a b
indexing :: Iso s t a b       -> IndexedLens Int s t a b
indexing :: Fold s a          -> IndexedFold Int s a
indexing :: Getter s a        -> IndexedGetter Int s a
indexing :: Indexable Int p => LensLike (Indexing f) s t a b -> Over p f s t a b

64-bit Indexing

newtype Indexing64 f a Source #

Applicative composition of State Int64 with a Functor, used by indexed64.

Constructors

Indexing64 

Fields

Instances

Functor f => Functor (Indexing64 f) Source # 

Methods

fmap :: (a -> b) -> Indexing64 f a -> Indexing64 f b #

(<$) :: a -> Indexing64 f b -> Indexing64 f a #

Applicative f => Applicative (Indexing64 f) Source # 

Methods

pure :: a -> Indexing64 f a #

(<*>) :: Indexing64 f (a -> b) -> Indexing64 f a -> Indexing64 f b #

liftA2 :: (a -> b -> c) -> Indexing64 f a -> Indexing64 f b -> Indexing64 f c #

(*>) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f b #

(<*) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f a #

Contravariant f => Contravariant (Indexing64 f) Source # 

Methods

contramap :: (a -> b) -> Indexing64 f b -> Indexing64 f a #

(>$) :: b -> Indexing64 f b -> Indexing64 f a #

Apply f => Apply (Indexing64 f) Source # 

Methods

(<.>) :: Indexing64 f (a -> b) -> Indexing64 f a -> Indexing64 f b #

(.>) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f b #

(<.) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f a #

liftF2 :: (a -> b -> c) -> Indexing64 f a -> Indexing64 f b -> Indexing64 f c #

indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t Source #

Transform a Traversal into an IndexedTraversal or a Fold into an IndexedFold, etc.

This combinator is like indexing except that it handles large traversals and folds gracefully.

indexing64 :: Traversal s t a b -> IndexedTraversal Int64 s t a b
indexing64 :: Prism s t a b     -> IndexedTraversal Int64 s t a b
indexing64 :: Lens s t a b      -> IndexedLens Int64 s t a b
indexing64 :: Iso s t a b       -> IndexedLens Int64 s t a b
indexing64 :: Fold s a          -> IndexedFold Int64 s a
indexing64 :: Getter s a        -> IndexedGetter Int64 s a
indexing64 :: Indexable Int64 p => LensLike (Indexing64 f) s t a b -> Over p f s t a b

Converting to Folds

withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t) Source #

Fold a container with indices returning both the indices and the values.

The result is only valid to compose in a Traversal, if you don't edit the index as edits to the index have no effect.

>>> [10, 20, 30] ^.. ifolded . withIndex
[(0,10),(1,20),(2,30)]
>>> [10, 20, 30] ^.. ifolded . withIndex . alongside negated (re _Show)
[(0,"10"),(-1,"20"),(-2,"30")]

asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s) Source #

When composed with an IndexedFold or IndexedTraversal this yields an (Indexed) Fold of the indices.