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

Safe HaskellNone
LanguageHaskell2010

Optics.IxAffineTraversal

Contents

Description

An IxAffineTraversal is an indexed version of an AffineTraversal. 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 IxAffineTraversal i s t a b = Optic An_AffineTraversal (WithIx i) s t a b Source #

Type synonym for a type-modifying indexed affine traversal.

type IxAffineTraversal' i s a = Optic' An_AffineTraversal (WithIx i) s a Source #

Type synonym for a type-preserving indexed affine traversal.

Introduction

iatraversal :: (s -> Either t (i, a)) -> (s -> b -> t) -> IxAffineTraversal i s t a b Source #

Build an indexed affine traversal from a matcher and an updater.

If you want to build an IxAffineTraversal from the van Laarhoven representation, use iatraversalVL.

Elimination

An IxAffineTraversal is in particular an IxAffineFold and an IxSetter, therefore you can specialise types to obtain:

ipreview :: IxAffineTraversal i s t a b -> s -> Maybe (i, a)
iover    :: IxAffineTraversal i s t a b -> (i -> a -> b) -> s -> t
iset     :: IxAffineTraversal i s t a b -> (i      -> b) -> s -> t

Subtyping

data An_AffineTraversal Source #

Tag for an affine traversal.

Instances
Is An_AffineTraversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_AffineTraversal An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_AffineTraversal 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 An_AffineTraversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Lens An_AffineTraversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_Iso An_AffineTraversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

ArrowChoice arr => ArrowOptic An_AffineTraversal arr Source # 
Instance details

Defined in Optics.Arrow

Methods

overA :: Optic An_AffineTraversal is s t a b -> arr a b -> arr s t Source #

ToReadOnly An_AffineTraversal s t a b Source # 
Instance details

Defined in Optics.ReadOnly

IxOptic An_AffineTraversal s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

van Laarhoven encoding

type IxAffineTraversalVL i s t a b = forall f. Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t Source #

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

Note: this isn't exactly van Laarhoven representation as there is no Pointed class (which would be a superclass of Applicative that contains pure but not <*>). You can interpret the first argument as a dictionary of Pointed that supplies the point function (i.e. the implementation of pure).

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

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

iatraversalVL :: IxAffineTraversalVL i s t a b -> IxAffineTraversal i s t a b Source #

Build an indexed affine traversal from the van Laarhoven representation.

toIxAtraversalVL :: (Is k An_AffineTraversal, is `HasSingleIndex` i) => Optic k is s t a b -> IxAffineTraversalVL i s t a b Source #

Convert an indexed affine traversal to its van Laarhoven representation.