optics-core-0.4: Optics as an abstract interface: core definitions
Safe HaskellNone
LanguageHaskell2010

Optics.IxTraversal

Description

An IxTraversal is an indexed version of a Traversal. See the "Indexed optics" section of the overview documentation in the Optics module of the main optics package for more details on indexed optics.

Synopsis

Formation

type IxTraversal i s t a b = Optic A_Traversal (WithIx i) s t a b Source #

Type synonym for a type-modifying indexed traversal.

type IxTraversal' i s a = Optic' A_Traversal (WithIx i) s a Source #

Type synonym for a type-preserving indexed traversal.

Introduction

itraversalVL :: IxTraversalVL i s t a b -> IxTraversal i s t a b Source #

Build an indexed traversal from the van Laarhoven representation.

itraversalVL . itraverseOfid
itraverseOf . itraversalVLid

Elimination

itraverseOf :: (Is k A_Traversal, Applicative f, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> a -> f b) -> s -> f t Source #

Map each element of a structure targeted by an IxTraversal (supplying the index), evaluate these actions from left to right, and collect the results.

This yields the van Laarhoven representation of an indexed traversal.

Computation

Well-formedness

itraverseOf o (const pure) ≡ pure
fmap (itraverseOf o f) . itraverseOf o g ≡ getCompose . itraverseOf o (\ i -> Compose . fmap (f i) . g i)

Additional introduction forms

See also each, which is an IxTraversal over each element of a (potentially monomorphic) container.

itraversed :: TraversableWithIndex i f => IxTraversal i (f a) (f b) a b Source #

Indexed traversal via the TraversableWithIndex class.

itraverseOf itraverseditraverse
>>> iover (itraversed <%> itraversed) (,) ["ab", "cd"]
[[((0,0),'a'),((0,1),'b')],[((1,0),'c'),((1,1),'d')]]

ignored :: IxAffineTraversal i s s a b Source #

This is the trivial empty IxAffineTraversal, i.e. the optic that targets no substructures.

This is the identity element when a Fold, AffineFold, IxFold, IxAffineFold, Traversal or IxTraversal is viewed as a monoid.

>>> 6 & ignored %~ absurd
6

elementsOf :: Is k A_Traversal => Optic k is s t a a -> (Int -> Bool) -> IxTraversal Int s t a a Source #

Traverse selected elements of a Traversal where their ordinal positions match a predicate.

elements :: Traversable f => (Int -> Bool) -> IxTraversal' Int (f a) a Source #

Traverse elements of a Traversable container where their ordinal positions match a predicate.

elementselementsOf traverse

elementOf :: Is k A_Traversal => Optic' k is s a -> Int -> IxAffineTraversal' Int s a Source #

Traverse the nth element of a Traversal if it exists.

element :: Traversable f => Int -> IxAffineTraversal' Int (f a) a Source #

Traverse the nth element of a Traversable container.

elementelementOf traversed

Additional elimination forms

iforOf :: (Is k A_Traversal, Applicative f, is `HasSingleIndex` i) => Optic k is s t a b -> s -> (i -> a -> f b) -> f t Source #

A version of itraverseOf with the arguments flipped.

imapAccumLOf :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc) Source #

Generalizes mapAccumL to an arbitrary IxTraversal.

imapAccumLOf accumulates state from left to right.

mapAccumLOf o ≡ imapAccumLOf o . const

imapAccumROf :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc) Source #

Generalizes mapAccumR to an arbitrary IxTraversal.

imapAccumROf accumulates state from right to left.

mapAccumROf o ≡ imapAccumROf o . const

iscanl1Of :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a a -> (i -> a -> a -> a) -> s -> t Source #

This permits the use of scanl1 over an arbitrary IxTraversal.

iscanr1Of :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a a -> (i -> a -> a -> a) -> s -> t Source #

This permits the use of scanr1 over an arbitrary IxTraversal.

ifailover :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> a -> b) -> s -> Maybe t Source #

Try to map a function which uses the index over this IxTraversal, returning Nothing if the IxTraversal has no targets.

ifailover' :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> a -> b) -> s -> Maybe t Source #

Version of ifailover strict in the application of the function.

Combinators

indices :: (Is k A_Traversal, is `HasSingleIndex` i) => (i -> Bool) -> Optic k is s t a a -> IxTraversal i s t a a Source #

Filter results of an IxTraversal that don't satisfy a predicate on the indices.

>>> toListOf (itraversed %& indices even) "foobar"
"foa"

ibackwards :: (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a b -> IxTraversal i s t a b Source #

This allows you to traverse the elements of an indexed traversal in the opposite order.

ipartsOf :: forall k is i s t a. (Is k A_Traversal, is `HasSingleIndex` i) => Optic k is s t a a -> IxLens [i] s t [a] [a] Source #

An indexed version of partsOf that receives the entire list of indices as its indices.

isingular :: forall k is i s a. (Is k A_Traversal, is `HasSingleIndex` i) => Optic' k is s a -> IxAffineTraversal' i s a Source #

Convert an indexed traversal to an IxAffineTraversal that visits the first element of the original traversal.

For the fold version see ipre.

>>> [1,2,3] & iover (isingular itraversed) (-)
[-1,2,3]

Since: 0.3

Monoid structure

IxTraversal admits a (partial) monoid structure where iadjoin combines non-overlapping indexed traversals, and the identity element is ignored (which traverses no elements).

If you merely need an IxFold, you can use indexed traversals as indexed folds and combine them with one of the monoid structures on indexed folds (see Optics.IxFold). In particular, isumming can be used to concatenate results from two traversals, and ifailing will returns results from the second traversal only if the first returns no results.

There is no Semigroup or Monoid instance for IxTraversal, because there is not a unique choice of monoid to use that works for all optics, and the (<>) operator could not be used to combine optics of different kinds.

iadjoin :: (Is k A_Traversal, Is l A_Traversal, is `HasSingleIndex` i) => Optic' k is s a -> Optic' l is s a -> IxTraversal' i s a infixr 6 Source #

Combine two disjoint indexed traversals into one.

>>> iover (_1 % itraversed `iadjoin` _2 % itraversed) (+) ([0, 0, 0], (3, 5))
([0,1,2],(3,8))

Note: if the argument traversals are not disjoint, the result will not respect the IxTraversal laws, because it will visit the same element multiple times. See section 7 of Understanding Idiomatic Traversals Backwards and Forwards by Bird et al. for why this is illegal.

>>> iview (ipartsOf (each `iadjoin` each)) ("x","y")
([0,1,0,1],["x","y","x","y"])
>>> iset (ipartsOf (each `iadjoin` each)) (const ["a","b","c","d"]) ("x","y")
("c","d")

For the IxFold version see isumming.

Since: 0.4

Subtyping

data A_Traversal :: OpticKind Source #

Tag for a traversal.

Instances

Instances details
Is A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Fold p => r Source #

Is A_Traversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Setter p => r Source #

Is An_AffineTraversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Traversal p => r Source #

Is A_Prism A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Traversal p => r Source #

Is A_Lens A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Traversal p => r Source #

Is An_Iso A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Fold A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Traversal p) => r) -> Constraints A_Fold p => r Source #

JoinKinds An_AffineFold A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Traversal p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_Getter A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Traversal p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_ReversedPrism A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Traversal p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_Setter A_Traversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Traversal p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Traversal A_Fold A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Fold p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_Traversal An_AffineFold A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineFold p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_Traversal A_Getter A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Getter p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_Traversal A_ReversedPrism A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_ReversedPrism p) => r) -> Constraints A_Fold p => r Source #

JoinKinds A_Traversal A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Traversal A_Traversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Traversal p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Traversal An_AffineTraversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineTraversal p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Traversal A_Prism A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Prism p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Traversal A_Lens A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Lens p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Traversal An_Iso A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_Iso p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds An_AffineTraversal A_Traversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Traversal p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Prism A_Traversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Traversal p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds A_Lens A_Traversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Traversal p) => r) -> Constraints A_Traversal p => r Source #

JoinKinds An_Iso A_Traversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Traversal p) => r) -> Constraints A_Traversal p => r Source #

ToReadOnly A_Traversal s t a b Source # 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Traversal Source #

Methods

getting :: forall (is :: IxList). Optic A_Traversal is s t a b -> Optic' (ReadOnlyOptic A_Traversal) is s a Source #

IxOptic A_Traversal s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Traversal is s t a b -> Optic A_Traversal NoIx s t a b Source #

type ReadOnlyOptic A_Traversal Source # 
Instance details

Defined in Optics.ReadOnly

van Laarhoven encoding

The van Laarhoven representation of an IxTraversal directly expresses how it lifts an effectful operation I -> A -> F B on elements and their indices to act on structures S -> F T. Thus itraverseOf converts an IxTraversal to an IxTraversalVL.

type IxTraversalVL i s t a b = forall f. Applicative f => (i -> a -> f b) -> s -> f t Source #

Type synonym for a type-modifying van Laarhoven indexed traversal.

type IxTraversalVL' i s a = IxTraversalVL i s s a a Source #

Type synonym for a type-preserving van Laarhoven indexed traversal.

Re-exports

class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where #

A Traversable with an additional index.

An instance must satisfy a (modified) form of the Traversable laws:

itraverse (const Identity) ≡ Identity
fmap (itraverse f) . itraverse g ≡ getCompose . itraverse (\i -> Compose . fmap (f i) . g i)

Minimal complete definition

Nothing

Methods

itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) #

Traverse an indexed container.

itraverseitraverseOf itraversed

Instances

Instances details
TraversableWithIndex Int [] 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> [a] -> f [b] #

TraversableWithIndex Int ZipList 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> ZipList a -> f (ZipList b) #

TraversableWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> NonEmpty a -> f (NonEmpty b) #

TraversableWithIndex Int IntMap 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> IntMap a -> f (IntMap b) #

TraversableWithIndex Int Seq 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) #

TraversableWithIndex () Maybe 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Maybe a -> f (Maybe b) #

TraversableWithIndex () Par1 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Par1 a -> f (Par1 b) #

TraversableWithIndex () Identity 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Identity a -> f (Identity b) #

TraversableWithIndex k (Map k) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b) #

TraversableWithIndex k ((,) k) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (k -> a -> f b) -> (k, a) -> f (k, b) #

Ix i => TraversableWithIndex i (Array i) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (i -> a -> f b) -> Array i a -> f (Array i b) #

TraversableWithIndex Void (V1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> V1 a -> f (V1 b) #

TraversableWithIndex Void (U1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> U1 a -> f (U1 b) #

TraversableWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Proxy a -> f (Proxy b) #

TraversableWithIndex i f => TraversableWithIndex i (Reverse f) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Reverse f a -> f0 (Reverse f b) #

TraversableWithIndex i f => TraversableWithIndex i (Rec1 f) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Rec1 f a -> f0 (Rec1 f b) #

TraversableWithIndex i m => TraversableWithIndex i (IdentityT m) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (i -> a -> f b) -> IdentityT m a -> f (IdentityT m b) #

TraversableWithIndex i f => TraversableWithIndex i (Backwards f) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Backwards f a -> f0 (Backwards f b) #

TraversableWithIndex Void (Const e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Const e a -> f (Const e b) #

TraversableWithIndex Void (Constant e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Constant e a -> f (Constant e b) #

TraversableWithIndex Void (K1 i c :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> K1 i c a -> f (K1 i c b) #

TraversableWithIndex [Int] Tree 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => ([Int] -> a -> f b) -> Tree a -> f (Tree b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Sum f g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Sum f g a -> f0 (Sum f g b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Product f g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Product f g a -> f0 (Product f g b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :+: g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :*: g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (Compose f g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => ((i, j) -> a -> f0 b) -> Compose f g a -> f0 (Compose f g b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (f :.: g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => ((i, j) -> a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) #