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

Safe HaskellNone
LanguageHaskell2010

Optics.IxSetter

Contents

Description

An IxSetter is an indexed version of an 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 Source #

Tag for a setter.

Instances
Is A_Traversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is An_AffineTraversal A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Prism A_Setter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Prism A_Setter p -> (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 :: proxy A_Lens A_Setter p -> (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 :: proxy An_Iso A_Setter p -> (Constraints An_Iso 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 :: 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 | f -> i where Source #

Class for Functors that have an additional read-only index available.

Minimal complete definition

Nothing

Methods

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

imap :: TraversableWithIndex i f => (i -> a -> b) -> f a -> f b Source #

Instances
FunctorWithIndex Int [] Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex Int NonEmpty Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex Int IntMap Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex Int Seq Source #

The position in the Seq is available as the index.

Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex k (Map k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex k ((,) k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

FunctorWithIndex [Int] Tree Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

Defined in Optics.Internal.Indexed

Methods

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