lens-1.6: Lenses, Folds and Traversals

Portabilityrank 2 types, MPTCs, TFs, flexible
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.Indexed

Contents

Description

 

Synopsis

Indexed Functions

class Indexed i k whereSource

Permit overloading of function application for things that also admit a notion of a key or index.

Provides overloading for indexed functions.

Methods

index :: ((i -> a) -> b) -> k a bSource

Build a function from an indexed function

Instances

Indexed i (->) 
~ * i j => Indexed i (Index j)

Using an equality witness to avoid potential overlapping instances and aid dispatch.

type Indexable i a b = forall k. Indexed i k => k a bSource

Type alias for passing around polymorphic indexed functions.

newtype Index i a b Source

A function with access to a index. This constructor may be useful when you need to store a HasIndex.

Constructors

Index 

Fields

withIndex :: (i -> a) -> b
 

Instances

~ * i j => Indexed i (Index j)

Using an equality witness to avoid potential overlapping instances and aid dispatch.

(.@) :: Indexed (i, j) k => Index i b c -> Index j a b -> k a cSource

Composition of indexed functions

icompose :: Indexed k r => (i -> j -> k) -> Index i b c -> Index j a b -> r a cSource

Composition of indexed functions with a user supplied function for combining indexs

reindex :: Indexed j k => (i -> j) -> Index i a b -> k a bSource

Remap the index.

Indexed Setter

type IndexedSetter i a b c d = forall f k. (Indexed i k, Settable f) => k (c -> f d) (a -> f b)Source

Every IndexedSetter is a valid Setter

The Setter laws are still required to hold.

imapOf :: Overloaded (Index i) Mutator a b c d -> (i -> c -> d) -> a -> bSource

Map with index

 imapOf :: IndexedTraversal i a b c d -> (i -> c -> d) -> a -> b
 imapOf :: IndexedSetter i a b c d -> (i -> c -> d) -> a -> b

(%@) :: Overloaded (Index i) Mutator a b c d -> (i -> c -> d) -> a -> bSource

 (%@) = imapOf

Indexed Traversals

type IndexedTraversal i a b c d = forall f k. (Indexed i k, Applicative f) => k (c -> f d) (a -> f b)Source

Every indexed traversal is a valid Traversal or indexed fold.

The Traversal laws are still required to hold.

itraverseOf :: Overloaded (Index i) f a b c d -> (i -> c -> f d) -> a -> f bSource

Traversal with an index.

 itraverseOf = withIndex
 itraverseOf :: IndexedTraversal i a b c d -> (i -> c -> f d) -> a -> f b

iforOf :: Overloaded (Index i) f a b c d -> a -> (i -> c -> f d) -> f bSource

 iforOf = flip . itraverseOf

imapMOf :: Overloaded (Index i) (WrappedMonad m) a b c d -> (i -> c -> m d) -> a -> m bSource

Map each element of a structure targeted by a lens to a monadic action, evaluate these actions from left to right, and collect the results, with access its position.

 imapMOf :: Monad m => IndexedTraversal a b c d -> (i -> c -> m d) -> a -> m b

iforMOf :: Overloaded (Index i) (WrappedMonad m) a b c d -> a -> (i -> c -> m d) -> m bSource

 iforMOf = flip . imapMOf

imapAccumROf :: Overloaded (Index i) (State s) a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)Source

Generalizes mapAccumR to an arbitrary IndexedTraversal.

imapAccumROf accumulates state from right to left.

imapAccumLOf :: Overloaded (Index i) (Backwards (State s)) a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)Source

Generalized mapAccumL to an arbitrary IndexedTraversal.

imapAccumLOf accumulates state from left to right.

Indexed Folds

type IndexedFold i a c = forall k f b d. (Indexed i k, Applicative f, Gettable f) => k (c -> f d) (a -> f b)Source

Every IndexedFold is a valid Fold.

type IndexedFolding i m a b c d = Index i (c -> Accessor m d) (a -> Accessor m b)Source

ifoldMapOf :: IndexedFolding i m a b c d -> (i -> c -> m) -> a -> mSource

 ifoldMapOf :: Monoid m => IndexedFold i a c          -> (i -> c -> m) -> a -> m
 ifoldMapOf :: Monoid m => IndexedTraversal i a b c d -> (i -> c -> m) -> a -> m

ifoldrOf :: IndexedFolding i (Endo e) a b c d -> (i -> c -> e -> e) -> e -> a -> eSource

Right-associative fold of parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.

 ifoldrOf :: IndexedFold i a c          -> (i -> c -> e -> e) -> e -> a -> e
 ifoldrOf :: IndexedTraversal i a b c d -> (i -> c -> e -> e) -> e -> a -> e

ifoldlOf :: IndexedFolding i (Dual (Endo e)) a b c d -> (i -> e -> c -> e) -> e -> a -> eSource

Left-associative fold of the parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.

 foldl = foldlOf folded
 ifoldlOf :: IndexedFold i a c          -> (i -> e -> c -> e) -> e -> a -> e
 ifoldlOf :: IndexedTraversal i a b c d -> (i -> e -> c -> e) -> e -> a -> e

ianyOf :: IndexedFolding i Any a b c d -> (i -> c -> Bool) -> a -> BoolSource

 ianyOf :: IndexedFold i a c          -> (i -> c -> Bool) -> a -> Bool
 ianyOf :: IndexedTraversal i a b c d -> (i -> c -> Bool) -> a -> Bool

iallOf :: IndexedFolding i All a b c d -> (i -> c -> Bool) -> a -> BoolSource

 iallOf :: IndexedFold i a c          -> (i -> c -> Bool) -> a -> Bool
 iallOf :: IndexedTraversal i a b c d -> (i -> c -> Bool) -> a -> Bool

itraverseOf_ :: Functor f => IndexedFolding i (Traversed f) a b c d -> (i -> c -> f e) -> a -> f ()Source

 itraverseOf_ :: Applicative f => IndexedFold i a c          -> (i -> c -> f e) -> a -> f ()
 itraverseOf_ :: Applicative f => IndexedTraversal i a b c d -> (i -> c -> f e) -> a -> f ()

iforOf_ :: Functor f => IndexedFolding i (Traversed f) a b c d -> a -> (i -> c -> f e) -> f ()Source

 iforOf_ :: Applicative f => IndexedFold i a c          -> a -> (i -> c -> f e) -> f ()
 iforOf_ :: Applicative f => IndexedTraversal i a b c d -> a -> (i -> c -> f e) -> f ()

imapMOf_ :: Monad m => IndexedFolding i (Sequenced m) a b c d -> (i -> c -> m e) -> a -> m ()Source

 imapMOf_ :: Monad m => IndexedFold i a c          -> (i -> c -> m e) -> a -> m ()
 imapMOf_ :: Monad m => IndexedTraversal i a b c d -> (i -> c -> m e) -> a -> m ()

iforMOf_ :: Monad m => IndexedFolding i (Sequenced m) a b c d -> a -> (i -> c -> m e) -> m ()Source

 iforMOf_ :: Monad m => IndexedFold i a c          -> a -> (i -> c -> m e) -> m ()
 iforMOf_ :: Monad m => IndexedTraversal i a b c d -> a -> (i -> c -> m e) -> m ()

iconcatMapOf :: IndexedFolding i [e] a b c d -> (i -> c -> [e]) -> a -> [e]Source

 iconcatMapOf :: IndexedFold i a c          -> (i -> c -> [e]) -> a -> [e]
 iconcatMapOf :: IndexedTraversal i a b c d -> (i -> c -> [e]) -> a -> [e]

ifoldrOf' :: IndexedFolding i (Dual (Endo (e -> e))) a b c d -> (i -> c -> e -> e) -> e -> a -> eSource

Strictly fold right over the elements of a structure with an index.

 ifoldrOf' :: IndexedFold i a c          -> (i -> c -> e -> e) -> e -> a -> e
 ifoldrOf' :: IndexedTraversal i a b c d -> (i -> c -> e -> e) -> e -> a -> e

ifoldlOf' :: IndexedFolding i (Endo (e -> e)) a b c d -> (i -> e -> c -> e) -> e -> a -> eSource

Fold over the elements of a structure with an index, associating to the left, but strictly.

 ifoldlOf' :: IndexedFold i a c            -> (i -> e -> c -> e) -> e -> a -> e
 ifoldlOf' :: IndexedTraversal i a b c d   -> (i -> e -> c -> e) -> e -> a -> e

ifoldrMOf :: Monad m => IndexedFolding i (Dual (Endo (e -> m e))) a b c d -> (i -> c -> e -> m e) -> e -> a -> m eSource

Monadic fold right over the elements of a structure with an index.

 ifoldrMOf :: Monad m => IndexedFold i a c          -> (i -> c -> e -> m e) -> e -> a -> e
 ifoldrMOf :: Monad m => IndexedTraversal i a b c d -> (i -> c -> e -> m e) -> e -> a -> e

ifoldlMOf :: Monad m => IndexedFolding i (Endo (e -> m e)) a b c d -> (i -> e -> c -> m e) -> e -> a -> m eSource

Monadic fold over the elements of a structure with an index, associating to the left.

 ifoldlOf' :: Monad m => IndexedFold i a c            -> (i -> e -> c -> m e) -> e -> a -> e
 ifoldlOf' :: Monad m => IndexedTraversal i a b c d   -> (i -> e -> c -> m e) -> e -> a -> e

Simple

type SimpleIndexedTraversal i a b = IndexedTraversal i a a b bSource

type SimpleIdexedTraversal i = Simple (IndexedTraversal i)

type SimpleIndexedSetter i a b = IndexedSetter i a a b bSource

type 'SimpleIdexedTraversal i = Simple (IndexedTraversal i)