optics-core-0.2: Optics as an abstract interface: core definitions

Safe HaskellNone
LanguageHaskell2010

Optics.Traversal

Contents

Description

A Traversal lifts an effectful operation on elements to act on structures containing those elements.

That is, given a function op :: A -> F B where F is Applicative, a Traversal S T A B can produce a function S -> F T that applies op to all the As contained in the S.

This can be seen as a generalisation of traverse, where the type S does not need to be a type constructor with A as the last parameter.

A Lens is a Traversal that acts on a single value.

A close relative is the AffineTraversal, which is a Traversal that acts on at most one value.

Synopsis

Formation

type Traversal s t a b = Optic A_Traversal NoIx s t a b Source #

Type synonym for a type-modifying traversal.

type Traversal' s a = Optic' A_Traversal NoIx s a Source #

Type synonym for a type-preserving traversal.

Introduction

traversalVL :: TraversalVL s t a b -> Traversal s t a b Source #

Build a traversal from the van Laarhoven representation.

traversalVL . traverseOfid
traverseOf . traversalVLid

Elimination

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

Map each element of a structure targeted by a Traversal, evaluate these actions from left to right, and collect the results.

Computation

Well-formedness

Additional introduction forms

traversed :: Traversable t => Traversal (t a) (t b) a b Source #

Construct a Traversal via the Traversable class.

traverseOf traversed = traverse

Additional elimination forms

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

A version of traverseOf with the arguments flipped.

sequenceOf :: (Is k A_Traversal, Applicative f) => Optic k is s t (f b) b -> s -> f t Source #

Evaluate each action in the structure from left to right, and collect the results.

>>> sequenceOf each ([1,2],[3,4])
[(1,3),(1,4),(2,3),(2,4)]
sequencesequenceOf traversedtraverse id
sequenceOf o ≡ traverseOf o id

transposeOf :: Is k A_Traversal => Optic k is s t [a] a -> s -> [t] Source #

This generalizes transpose to an arbitrary Traversal.

Note: transpose handles ragged inputs more intelligently, but for non-ragged inputs:

>>> transposeOf traversed [[1,2,3],[4,5,6]]
[[1,4],[2,5],[3,6]]
transposetransposeOf traverse

mapAccumROf :: Is k A_Traversal => Optic k is s t a b -> (acc -> a -> (b, acc)) -> acc -> s -> (t, acc) Source #

This generalizes mapAccumR to an arbitrary Traversal.

mapAccumRmapAccumROf traversed

mapAccumROf accumulates State from right to left.

mapAccumLOf :: Is k A_Traversal => Optic k is s t a b -> (acc -> a -> (b, acc)) -> acc -> s -> (t, acc) Source #

This generalizes mapAccumL to an arbitrary Traversal.

mapAccumLmapAccumLOf traverse

mapAccumLOf accumulates State from left to right.

scanr1Of :: Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t Source #

This permits the use of scanr1 over an arbitrary Traversal.

scanr1scanr1Of traversed

scanl1Of :: Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t Source #

This permits the use of scanl1 over an arbitrary Traversal.

scanl1scanl1Of traversed

failover :: Is k A_Traversal => Optic k is s t a b -> (a -> b) -> s -> Maybe t Source #

Try to map a function over this Traversal, returning Nothing if the traversal has no targets.

>>> failover (element 3) (*2) [1,2]
Nothing
>>> failover _Left (*2) (Right 4)
Nothing
>>> failover _Right (*2) (Right 4)
Just (Right 8)

failover' :: Is k A_Traversal => Optic k is s t a b -> (a -> b) -> s -> Maybe t Source #

Version of failover strict in the application of f.

Combinators

backwards :: Is k A_Traversal => Optic k is s t a b -> Traversal s t a b Source #

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

partsOf :: forall k is s t a. Is k A_Traversal => Optic k is s t a a -> Lens s t [a] [a] Source #

partsOf turns a Traversal into a Lens.

Note: You should really try to maintain the invariant of the number of children in the list.

>>> ('a','b','c') & partsOf each .~ ['x','y','z']
('x','y','z')

Any extras will be lost. If you do not supply enough, then the remainder will come from the original structure.

>>> ('a','b','c') & partsOf each .~ ['w','x','y','z']
('w','x','y')
>>> ('a','b','c') & partsOf each .~ ['x','y']
('x','y','c')
>>> ('b', 'a', 'd', 'c') & partsOf each %~ sort
('a','b','c','d')

So technically, this is only a Lens if you do not change the number of results it returns.

Subtyping

data A_Traversal :: OpticKind Source #

Tag for a traversal.

Instances
Is A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Traversal A_Fold p -> (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

Is An_AffineTraversal A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Prism A_Traversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Prism A_Traversal p -> (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 :: proxy A_Lens A_Traversal p -> (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 :: proxy An_Iso A_Traversal p -> (Constraints An_Iso p -> r) -> Constraints A_Traversal p -> r Source #

ToReadOnly A_Traversal s t a b Source # 
Instance details

Defined in Optics.ReadOnly

Methods

getting :: Optic A_Traversal is s t a b -> Optic' (Join A_Getter A_Traversal) is s a Source #

IxOptic A_Traversal s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Traversal is s t a b -> Optic A_Traversal NoIx s t a b Source #

van Laarhoven encoding

The van Laarhoven representation of a Traversal directly expresses how it lifts an effectful operation A -> F B on elements to act on structures S -> F T. Thus traverseOf converts a Traversal to a TraversalVL.

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

Type synonym for a type-modifying van Laarhoven traversal.

type TraversalVL' s a = TraversalVL s s a a Source #

Type synonym for a type-preserving van Laarhoven traversal.