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

Optics.ReversedPrism

Description

A ReversedPrism is a backwards Prism, i.e. a ReversedPrism s t a b is equivalent to a Prism b a t s. These are typically produced by calling re on a Prism. They are distinguished from a Getter so that re . re on a Prism returns a Prism.

Synopsis

Formation

type ReversedPrism s t a b = Optic A_ReversedPrism NoIx s t a b Source #

Type synonym for a type-modifying reversed prism.

type ReversedPrism' s a = Optic' A_ReversedPrism NoIx s a Source #

Type synonym for a type-preserving reversed prism.

Introduction

There is no canonical introduction form for ReversedPrism, but you can use re to construct one from a Prism:

(\ f g -> re (prism f g)) :: (s -> a) -> (b -> Either a t) -> ReversedPrism s t a b

Elimination

A ReversedPrism is a Getter, so you can specialise types to obtain:

view :: ReversedPrism' s a -> s -> a

There is no reversed matching defined, but it is definable using re:

matching . re :: ReversedPrism s t a b -> b -> Either a t

Computation

view          $ re (prism f g) ≡ f
matching . re $ re (prism f g) ≡ g

Subtyping

data A_ReversedPrism :: OpticKind Source #

Tag for a reversed prism.

Instances

Instances details
ReversibleOptic A_ReversedPrism Source # 
Instance details

Defined in Optics.Re

Associated Types

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

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_ReversedPrism is s t a b -> Optic (ReversedOptic A_ReversedPrism) is b a t s Source #

Is A_ReversedPrism A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Fold p => r Source #

Is A_ReversedPrism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints An_AffineFold p => r Source #

Is A_ReversedPrism A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Getter p => r Source #

Is An_Iso A_ReversedPrism 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_ReversedPrism p => r Source #

JoinKinds A_Fold A_ReversedPrism A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds An_AffineFold A_ReversedPrism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_Getter A_ReversedPrism A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism A_Fold A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism An_AffineFold An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism A_Getter A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism A_ReversedPrism A_ReversedPrism Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

JoinKinds A_ReversedPrism A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism An_AffineTraversal An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

JoinKinds A_ReversedPrism A_Prism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism A_Lens A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_ReversedPrism An_Iso A_ReversedPrism Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_Traversal A_ReversedPrism A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds An_AffineTraversal A_ReversedPrism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

JoinKinds A_Prism A_ReversedPrism An_AffineFold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds A_Lens A_ReversedPrism A_Getter Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

JoinKinds An_Iso A_ReversedPrism A_ReversedPrism Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

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

ToReadOnly A_ReversedPrism s t a b Source # 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_ReversedPrism Source #

Methods

getting :: forall (is :: IxList). Optic A_ReversedPrism is s t a b -> Optic' (ReadOnlyOptic A_ReversedPrism) is s a 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 #

type ReversedOptic A_ReversedPrism Source # 
Instance details

Defined in Optics.Re

type ReadOnlyOptic A_ReversedPrism Source # 
Instance details

Defined in Optics.ReadOnly

type MappedOptic A_ReversedPrism Source # 
Instance details

Defined in Optics.Mapping