| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Optics.Optic
Description
This module provides core definitions:
- an opaque Optictype, which is parameterised over a type representing an optic kind (instantiated with tag types such asA_Lens);
- the optic composition operator (%);
- the subtyping relation Iswith an accompanyingcastOpticfunction to convert an optic kind;
- the Joinoperation used to find the optic kind resulting from a composition.
Each optic kind is identified by a "tag type" (such as A_Lens), which is an
 empty data type.  The type of the actual optics (such as Lens)
 is obtained by applying Optic to the tag type.
See the Optics module in the main optics package for overview
 documentation.
Synopsis
- data Optic (k :: *) (is :: [*]) s t a b
- type Optic' k is s a = Optic k is s s a a
- 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
- class Is k l
- type family Join (k :: *) (l :: *) where ...
- (%) :: (Is k m, Is l m, m ~ Join k l, ks ~ Append is js) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
- (%%) :: forall k is js ks s t u v a b. ks ~ Append is js => Optic k is s t u v -> Optic k js u v a b -> Optic k ks s t a b
- (%&) :: 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'
- type NoIx = '[]
- type WithIx i = '[i]
- type family Append (xs :: [*]) (ys :: [*]) :: [*] where ...
- class NonEmptyIndices (is :: [*])
- class is ~ '[i] => HasSingleIndex (is :: [*]) (i :: *)
- class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: [*])
- (&) :: a -> (a -> b) -> b
- (<&>) :: Functor f => f a -> (a -> b) -> f b
Documentation
data Optic (k :: *) (is :: [*]) 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.
Instances
| (LabelOptic name k s t a b, is ~ NoIx) => IsLabel name (Optic k is s t a b) Source # | |
| Defined in Optics.Internal.Optic | |
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.
Subtyping
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 #
Subtyping relationship between kinds of optics.
An instance of Is k lOptic kOptic lIs A_Lens
 A_TraversalIs A_Traversal A_Lens
This class needs instances for all possible combinations of tags.
Minimal complete definition
Instances
type family Join (k :: *) (l :: *) where ... Source #
Computes the least upper bound of two optics kinds.
Join k l represents the least upper bound of an Optic k and an Optic
 l. This means in particular that composition of an Optic k and an Optic
 k will yield an Optic (Join k l).
Equations
Composition
(%) :: (Is k m, Is l m, m ~ Join k l, ks ~ Append is js) => 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. ks ~ Append is js => 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"]
Indexed optics
type family Append (xs :: [*]) (ys :: [*]) :: [*] where ... Source #
Append two type-level lists together.
class NonEmptyIndices (is :: [*]) Source #
Check whether a list of indices is not empty and generate sensible error message if it's not.
Instances
| (TypeError (Text "Indexed optic is expected") :: Constraint) => NonEmptyIndices ([] :: [Type]) Source # | |
| Defined in Optics.Internal.Indexed | |
| NonEmptyIndices (x ': xs) Source # | |
| Defined in Optics.Internal.Indexed | |
class is ~ '[i] => HasSingleIndex (is :: [*]) (i :: *) Source #
Generate sensible error messages in case a user tries to pass either an unindexed optic or indexed optic with unflattened indices where indexed optic with a single index is expected.
Instances
| ((TypeError (Text "Indexed optic is expected") :: Constraint), ([] :: [Type]) ~ (i ': ([] :: [Type]))) => HasSingleIndex ([] :: [Type]) i Source # | |
| Defined in Optics.Internal.Indexed | |
| ((TypeError (Text "Use icomposeN to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))) i Source # | |
| Defined in Optics.Internal.Indexed | |
| ((TypeError (Text "Use icompose5 to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) i Source # | |
| Defined in Optics.Internal.Indexed | |
| ((TypeError (Text "Use icompose4 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) i Source # | |
| Defined in Optics.Internal.Indexed | |
| ((TypeError (Text "Use icompose3 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': ([] :: [Type])))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': ([] :: [Type])))) i Source # | |
| Defined in Optics.Internal.Indexed | |
| ((TypeError (Text "Use (<%>) or icompose to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': ([] :: [Type]))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': ([] :: [Type]))) i Source # | |
| Defined in Optics.Internal.Indexed | |
| HasSingleIndex (i ': ([] :: [Type])) i Source # | |
| Defined in Optics.Internal.Indexed | |
class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: [*]) Source #
Show useful error message when a function expects optics without indices.
Instances
| AcceptsEmptyIndices f ([] :: [Type]) Source # | |
| Defined in Optics.Internal.Indexed | |
| ((TypeError ((Text "\8216" :<>: Text f) :<>: Text "\8217 accepts only optics with no indices") :: Constraint), (x ': xs) ~ NoIx) => AcceptsEmptyIndices f (x ': xs) Source # | |
| Defined in Optics.Internal.Indexed | |