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

Safe HaskellNone
LanguageHaskell2010

Optics.Getter

Contents

Description

A Getter is simply a function considered as an Optic.

Given a function f :: S -> A, we can convert it into a Getter S A using to, and convert back to a function using view.

This is typically useful not when you have functions/Getters alone, but when you are composing multiple Optics to produce a Getter.

Synopsis

Formation

type Getter s a = Optic' A_Getter NoIx s a Source #

Type synonym for a getter.

Introduction

to :: (s -> a) -> Getter s a Source #

Build a getter from a function.

Elimination

view :: Is k A_Getter => Optic' k is s a -> s -> a Source #

View the value pointed to by a getter.

If you want to view a type-modifying optic that is insufficiently polymorphic to be type-preserving, use getting.

views :: Is k A_Getter => Optic' k is s a -> (a -> r) -> s -> r Source #

View the function of the value pointed to by a getter.

Computation

view (to f) ≡ f

Well-formedness

A Getter is not subject to any laws.

Subtyping

data A_Getter :: OpticKind Source #

Tag for a getter.

Instances
ReversibleOptic A_Getter Source # 
Instance details

Defined in Optics.Re

Associated Types

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

Methods

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

Is A_Getter A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

Is A_Getter An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_ReversedPrism A_Getter 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 :: (Constraints A_Lens p -> r) -> Constraints A_Getter p -> r Source #

Is An_Iso A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

(s ~ t, a ~ b) => ToReadOnly A_Getter s t a b Source # 
Instance details

Defined in Optics.ReadOnly

Methods

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

(s ~ t, a ~ b) => IxOptic A_Getter s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Getter is s t a b -> Optic A_Getter NoIx s t a 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 :: Type Source #

Methods

mapping :: 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 #

type ReversedOptic A_Getter Source # 
Instance details

Defined in Optics.Re

type MappedOptic A_Getter Source # 
Instance details

Defined in Optics.Mapping