optics-core-0.4: Optics as an abstract interface: core definitions
Safe HaskellNone
LanguageHaskell2010

Optics.IxSetter

Description

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

Type synonym for a type-modifying indexed setter.

type IxSetter' i s a = Optic' A_Setter (WithIx i) s a Source #

Type synonym for a type-preserving indexed setter.

Introduction

isets :: ((i -> a -> b) -> s -> t) -> IxSetter i s t a b Source #

Build an indexed setter from a function to modify the element(s).

Elimination

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

Apply an indexed setter as a modifier.

Computation

iover (isets f) ≡ f

Well-formedness

Additional introduction forms

imapped :: FunctorWithIndex i f => IxSetter i (f a) (f b) a b Source #

Indexed setter via the FunctorWithIndex class.

iover imappedimap

Additional elimination forms

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

Apply an indexed setter.

iset o f ≡ iover o (i _ -> f i)

iset' :: (Is k A_Setter, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> b) -> s -> t Source #

Apply an indexed setter, strictly.

iover' :: (Is k A_Setter, is `HasSingleIndex` i) => Optic k is s t a b -> (i -> a -> b) -> s -> t Source #

Apply an indexed setter as a modifier, strictly.

Subtyping

data A_Setter :: OpticKind Source #

Tag for a setter.

Instances

Instances details
Is A_Traversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Setter p => r Source #

Is An_AffineTraversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Setter p => r Source #

Is A_Prism A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Setter p => r Source #

Is A_Lens A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Setter p => r Source #

Is An_Iso A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Setter A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Setter A_Traversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Traversal p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Setter An_AffineTraversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_AffineTraversal p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Setter A_Prism A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Prism p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Setter A_Lens A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Lens p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Setter An_Iso A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_Iso p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Traversal A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

JoinKinds An_AffineTraversal A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Prism A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

JoinKinds A_Lens A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

JoinKinds An_Iso A_Setter A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Setter p) => r) -> Constraints A_Setter p => r Source #

IxOptic A_Setter s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Setter is s t a b -> Optic A_Setter NoIx s t a b Source #

Re-exports

class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where #

A Functor with an additional index.

Instances must satisfy a modified form of the Functor laws:

imap f . imap g ≡ imap (\i -> f i . g i)
imap (\_ a -> a) ≡ id

Minimal complete definition

Nothing

Methods

imap :: (i -> a -> b) -> f a -> f b #

Map with access to the index.

Instances

Instances details
FunctorWithIndex Int []

The position in the list is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> [a] -> [b] #

FunctorWithIndex Int ZipList

Same instance as for [].

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> ZipList a -> ZipList b #

FunctorWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> NonEmpty a -> NonEmpty b #

FunctorWithIndex Int IntMap 
Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> IntMap a -> IntMap b #

FunctorWithIndex Int Seq

The position in the Seq is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b #

FunctorWithIndex () Maybe 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Maybe a -> Maybe b #

FunctorWithIndex () Par1 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Par1 a -> Par1 b #

FunctorWithIndex () Identity 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Identity a -> Identity b #

FunctorWithIndex k (Map k) 
Instance details

Defined in WithIndex

Methods

imap :: (k -> a -> b) -> Map k a -> Map k b #

FunctorWithIndex k ((,) k) 
Instance details

Defined in WithIndex

Methods

imap :: (k -> a -> b) -> (k, a) -> (k, b) #

Ix i => FunctorWithIndex i (Array i) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Array i a -> Array i b #

FunctorWithIndex Void (V1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> V1 a -> V1 b #

FunctorWithIndex Void (U1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> U1 a -> U1 b #

FunctorWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Proxy a -> Proxy b #

FunctorWithIndex i f => FunctorWithIndex i (Reverse f) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Reverse f a -> Reverse f b #

FunctorWithIndex i f => FunctorWithIndex i (Rec1 f) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Rec1 f a -> Rec1 f b #

FunctorWithIndex i m => FunctorWithIndex i (IdentityT m) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> IdentityT m a -> IdentityT m b #

FunctorWithIndex i f => FunctorWithIndex i (Backwards f) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Backwards f a -> Backwards f b #

FunctorWithIndex Void (Const e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Const e a -> Const e b #

FunctorWithIndex Void (Constant e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Constant e a -> Constant e b #

FunctorWithIndex r ((->) r :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (r -> a -> b) -> (r -> a) -> r -> b #

FunctorWithIndex Void (K1 i c :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> K1 i c a -> K1 i c b #

FunctorWithIndex [Int] Tree 
Instance details

Defined in WithIndex

Methods

imap :: ([Int] -> a -> b) -> Tree a -> Tree b #

FunctorWithIndex i m => FunctorWithIndex (e, i) (ReaderT e m) 
Instance details

Defined in WithIndex

Methods

imap :: ((e, i) -> a -> b) -> ReaderT e m a -> ReaderT e m b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Sum f g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> Sum f g a -> Sum f g b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Product f g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> Product f g a -> Product f g b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :+: g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> (f :+: g) a -> (f :+: g) b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :*: g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> (f :*: g) a -> (f :*: g) b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (Compose f g) 
Instance details

Defined in WithIndex

Methods

imap :: ((i, j) -> a -> b) -> Compose f g a -> Compose f g b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (f :.: g) 
Instance details

Defined in WithIndex

Methods

imap :: ((i, j) -> a -> b) -> (f :.: g) a -> (f :.: g) b #