lens-1.5: 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

composeWithIndex :: 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 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.

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

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

foldrWithIndexOf :: 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.

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

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.

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

 traverseWithIndexOf :: IndexedTraversal i a b c d -> (i -> c -> f d) -> a -> f b

mapMWithIndexOf :: 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.

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

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 indexed Setter is a valid Setter

The Setter laws are still required to hold.

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

Map with index

 mapWithIndexOf :: IndexedSetter i a b c d -> (i -> c -> d) -> a -> b

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

 (%@) = mapWithIndexOf

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)