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

Safe HaskellNone
LanguageHaskell2010

Optics.AffineFold

Contents

Description

An AffineFold is a Fold that contains at most one element, or a Getter where the function may be partial.

Synopsis

Formation

type AffineFold s a = Optic' An_AffineFold NoIx s a Source #

Type synonym for an affine fold.

Introduction

afolding :: (s -> Maybe a) -> AffineFold s a Source #

Create an AffineFold from a partial function.

>>> preview (afolding listToMaybe) "foo"
Just 'f'

Elimination

preview :: Is k An_AffineFold => Optic' k is s a -> s -> Maybe a Source #

Retrieve the value targeted by an AffineFold.

>>> let _Right = prism Right $ either (Left . Left) Right
>>> preview _Right (Right 'x')
Just 'x'
>>> preview _Right (Left 'y')
Nothing

previews :: Is k An_AffineFold => Optic' k is s a -> (a -> r) -> s -> Maybe r Source #

Retrieve a function of the value targeted by an AffineFold.

Computation

preview (afolding f) ≡ f

Additional introduction forms

filtered :: (a -> Bool) -> AffineFold a a Source #

Filter result(s) of a fold that don't satisfy a predicate.

Additional elimination forms

isn't :: Is k An_AffineFold => Optic' k is s a -> s -> Bool Source #

Check to see if this AffineFold doesn't match.

>>> isn't _Just Nothing
True

Semigroup structure

afailing :: (Is k An_AffineFold, Is l An_AffineFold) => Optic' k is s a -> Optic' l js s a -> AffineFold s a infixl 3 Source #

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

>>> preview (ix 1 % re _Left `afailing` ix 2 % re _Right) [0,1,2,3]
Just (Left 1)
>>> preview (ix 42 % re _Left `afailing` ix 2 % re _Right) [0,1,2,3]
Just (Right 2)

Note: There is no summing equivalent, because asumming = afailing.

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 #