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

Optics.Internal.Optic

Contents

Description

Core optic types and subtyping machinery.

This module contains the core Optic types, and the underlying machinery that we need in order to implement the subtyping between various different flavours of optics.

The composition operator for optics is also defined here.

This module is intended for internal use only, and may change without warning in subsequent releases.

Synopsis

Documentation

newtype Optic (k :: OpticKind) (is :: IxList) s t a b Source #

Wrapper newtype for the whole family of optics.

The first parameter k identifies the particular optic kind (e.g. A_Lens or A_Traversal).

The parameter is is a list of types available as indices. This will typically be NoIx for unindexed optics, or WithIx for optics with a single index. See the "Indexed optics" section of the overview documentation in the Optics module of the main optics package for more details.

The parameters s and t represent the "big" structure, whereas a and b represent the "small" structure.

Constructors

Optic (forall p i. Profunctor p => Optic_ k p i (Curry is i) s t a b) 

Instances

Instances details
(LabelOptic name k s t a b, is ~ NoIx) => IsLabel name (Optic k is s t a b) Source # 
Instance details

Defined in Optics.Label

Methods

fromLabel :: Optic k is s t a b #

type Optic' k is s a = Optic k is s s a a Source #

Common special case of Optic where source and target types are equal.

Here, we need only one "big" and one "small" type. For lenses, this means that in the restricted form we cannot do type-changing updates.

type Optic_ k p i j s t a b = Constraints k p => Optic__ p i j s t a b Source #

Type representing the various kinds of optics.

The tag parameter k is translated into constraints on p via the type family Constraints.

type Optic__ p i j s t a b = p i a b -> p j s t Source #

Optic internally as a profunctor transformation.

getOptic :: Profunctor p => Optic k is s t a b -> Optic_ k p i (Curry is i) s t a b Source #

Strip the newtype wrapper off.

castOptic :: forall destKind srcKind is s t a b. Is srcKind destKind => Optic srcKind is s t a b -> Optic destKind is s t a b Source #

Explicit cast from one optic flavour to another.

The resulting optic kind is given in the first type argument, so you can use TypeApplications to set it. For example

 castOptic @A_Lens o

turns o into a Lens.

This is the identity function, modulo some constraint jiggery-pokery.

(%) :: forall k l m is js ks s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b infixl 9 Source #

Compose two optics of compatible flavours.

Returns an optic of the appropriate supertype. If either or both optics are indexed, the composition preserves all the indices.

(%%) :: forall k is js ks s t u v a b. AppendIndices is js ks => Optic k is s t u v -> Optic k js u v a b -> Optic k ks s t a b infixl 9 Source #

Compose two optics of the same flavour.

Normally you can simply use (%) instead, but this may be useful to help type inference if the type of one of the optics is otherwise under-constrained.

(%&) :: Optic k is s t a b -> (Optic k is s t a b -> Optic l js s' t' a' b') -> Optic l js s' t' a' b' infixl 9 Source #

Flipped function application, specialised to optics and binding tightly.

Useful for post-composing optics transformations:

>>> toListOf (ifolded %& ifiltered (\i s -> length s <= i)) ["", "a","abc"]
["","a"]

Re-exports