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

Safe HaskellNone
LanguageHaskell2010

Optics.IxLens

Contents

Description

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

Type synonym for a type-modifying indexed lens.

type IxLens' i s a = Optic' A_Lens (WithIx i) s a Source #

Type synonym for a type-preserving indexed lens.

Introduction

ilens :: (s -> (i, a)) -> (s -> b -> t) -> IxLens i s t a b Source #

Build an indexed lens from a getter and a setter.

If you want to build an IxLens from the van Laarhoven representation, use ilensVL.

Elimination

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

iview :: IxLens i s t a b -> s -> (i, a)
iover :: IxLens i s t a b -> (i -> a -> b) -> s -> t
iset  :: IxLens i s t a b -> (i      -> b) -> s -> t

Additional introduction forms

devoid :: IxLens' i Void a Source #

There is an indexed field for every type in the Void.

>>> set (mapped % devoid) 1 []
[]
>>> over (_Just % devoid) abs Nothing
Nothing

Subtyping

data A_Lens Source #

Tag for a lens.

Instances
ReversibleOptic A_Lens Source # 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Lens = (r :: Type) Source #

Methods

re :: AcceptsEmptyIndices "re" is => Optic A_Lens is s t a b -> Optic (ReversedOptic A_Lens) is b a t s Source #

Is A_Lens A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Lens A_Fold p -> (Constraints A_Lens p -> r) -> Constraints A_Fold p -> r Source #

Is A_Lens An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Lens A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Lens A_Getter p -> (Constraints A_Lens p -> r) -> Constraints A_Getter p -> r Source #

Is A_Lens A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Lens A_Setter p -> (Constraints A_Lens p -> r) -> Constraints A_Setter 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 A_Lens An_AffineTraversal Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_Iso A_Lens Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy An_Iso A_Lens p -> (Constraints An_Iso p -> r) -> Constraints A_Lens p -> r Source #

Arrow arr => ArrowOptic A_Lens arr Source # 
Instance details

Defined in Optics.Arrow

Methods

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

ToReadOnly A_Lens s t a b Source # 
Instance details

Defined in Optics.ReadOnly

Methods

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

IxOptic A_Lens s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

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

type ReversedOptic A_Lens Source # 
Instance details

Defined in Optics.Re

van Laarhoven encoding

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

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

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

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

ilensVL :: IxLensVL i s t a b -> IxLens i s t a b Source #

Build an indexed lens from the van Laarhoven representation.

toIxLensVL :: (Is k A_Lens, is `HasSingleIndex` i) => Optic k is s t a b -> IxLensVL i s t a b Source #

Convert an indexed lens to its van Laarhoven representation.

withIxLensVL :: (Is k A_Lens, is `HasSingleIndex` i) => Optic k is s t a b -> (IxLensVL i s t a b -> r) -> r Source #

Work with an indexed lens in the van Laarhoven representation.