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

Optics.Mapping

Description

This module defines mapping, which turns an Optic' k NoIx s a into an Optic' (MappedOptic k) NoIx (f s) (f a), in other words optic operating on values in a Functor.

Synopsis

Documentation

class MappingOptic k f g s t a b where Source #

Class for optics supporting mapping through a Functor.

Since: 0.3

Associated Types

type MappedOptic k Source #

Type family that maps an optic to the optic kind produced by mapping using it.

Methods

mapping :: "mapping" `AcceptsEmptyIndices` is => Optic k is s t a b -> Optic (MappedOptic k) is (f s) (g t) (f a) (g b) Source #

The mapping can be used to lift optic through a Functor.

mapping :: Iso    s t a b -> Iso    (f s) (g t) (f a) (g b)
mapping :: Lens   s   a   -> Getter (f s)       (f a)
mapping :: Getter s   a   -> Getter (f s)       (f a)
mapping :: Prism    t   b -> Review       (g t)       (g b)
mapping :: Review   t   b -> Review       (g t)       (g b)

Instances

Instances details
(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Review f g s t a b Source # 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Review Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Review is s t a b -> Optic (MappedOptic A_Review) is (f s) (g t) (f a) (g b) Source #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedLens f g s t a b Source # 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_ReversedLens Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_ReversedLens is s t a b -> Optic (MappedOptic A_ReversedLens) is (f s) (g t) (f a) (g b) Source #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Getter f g s t a b Source #
>>> [('a', True), ('b', False)] ^. _1 %& mapping
"ab"
>>> let v = [[ (('a', True), "foo"), (('b', False), "bar")], [ (('c', True), "xyz") ] ]
>>> v ^. _1 % _2 %& mapping %& mapping
[[True,False],[True]]
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Getter Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Getter is s t a b -> Optic (MappedOptic A_Getter) is (f s) (g t) (f a) (g b) Source #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedPrism f g s t a b Source # 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_ReversedPrism Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_ReversedPrism is s t a b -> Optic (MappedOptic A_ReversedPrism) is (f s) (g t) (f a) (g b) Source #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Prism f g s t a b Source # 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Prism Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Prism is s t a b -> Optic (MappedOptic A_Prism) is (f s) (g t) (f a) (g b) Source #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Lens f g s t a b Source # 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Lens Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Lens is s t a b -> Optic (MappedOptic A_Lens) is (f s) (g t) (f a) (g b) Source #

(Functor f, Functor g) => MappingOptic An_Iso f g s t a b Source # 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic An_Iso Source #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic An_Iso is s t a b -> Optic (MappedOptic An_Iso) is (f s) (g t) (f a) (g b) Source #