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

Safe HaskellNone
LanguageHaskell2010

Optics.IxAffineFold

Contents

Description

An IxAffineFold is an indexed version of an AffineFold. 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 IxAffineFold i s a = Optic' An_AffineFold (WithIx i) s a Source #

Type synonym for an indexed affine fold.

Introduction

iafolding :: (s -> Maybe (i, a)) -> IxAffineFold i s a Source #

Create an IxAffineFold from a partial function.

Elimination

ipreview :: (Is k An_AffineFold, is `HasSingleIndex` i) => Optic' k is s a -> s -> Maybe (i, a) Source #

Retrieve the value along with its index targeted by an IxAffineFold.

ipreviews :: (Is k An_AffineFold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> r) -> s -> Maybe r Source #

Retrieve a function of the value and its index targeted by an IxAffineFold.

Computation

ipreview (iafolding f) ≡ f

Additional introduction forms

iafoldVL :: (forall f. Functor f => (forall r. r -> f r) -> (i -> a -> f u) -> s -> f v) -> IxAffineFold i s a Source #

Obtain an IxAffineFold by lifting itraverse_ like function.

aifoldVL . iatraverseOf_id
aitraverseOf_ . iafoldVLid

Since: 0.3

Additional elimination forms

iatraverseOf_ :: (Is k An_AffineFold, Functor f, is `HasSingleIndex` i) => Optic' k is s a -> (forall r. r -> f r) -> (i -> a -> f u) -> s -> f () Source #

Traverse over the target of an IxAffineFold, computing a Functor-based answer, but unlike iatraverseOf do not construct a new structure.

Since: 0.3

Combinators

filteredBy :: Is k An_AffineFold => Optic' k is a i -> IxAffineFold i a a Source #

Obtain a potentially empty IxAffineFold by taking the element from another AffineFold and using it as an index.

Since: 0.3

Monoid structure

IxAffineFold admits a monoid structure where iafailing combines folds (returning a result from the second fold only if the first returns none) and the identity element is ignored (which returns no results).

Note: There is no isumming equivalent that returns an IxAffineFold, because it would not need to return more than one result.

There is no Semigroup or Monoid instance for IxAffineFold, 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.

iafailing :: (Is k An_AffineFold, Is l An_AffineFold, is1 `HasSingleIndex` i, is2 `HasSingleIndex` i) => Optic' k is1 s a -> Optic' l is2 s a -> IxAffineFold i s a infixl 3 Source #

Try the first IxAffineFold. If it returns no entry, try the second one.

Subtyping

data An_AffineFold :: OpticKind Source #

Tag for an affine fold.

Instances
Is An_AffineFold A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Getter An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_ReversedPrism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_AffineTraversal An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Prism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Lens An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_Iso An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

(s ~ t, a ~ b) => ToReadOnly An_AffineFold s t a b Source # 
Instance details

Defined in Optics.ReadOnly

(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

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