Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype Optic (k :: OpticKind) (is :: IxList) s t a b = Optic {
- getOptic :: forall p i. Profunctor p => Optic_ k p i (Curry is i) s t a b
- type Optic' k is s a = Optic k is s s a a
- type Optic_ k p i j s t a b = Constraints k p => Optic__ p i j s t a b
- type Optic__ p i j s t a b = p i a b -> p j s t
- 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
- (%) :: (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'
- class LabelOptic (name :: Symbol) k s t a b | name s -> k a, name t -> k b, name s b -> t, name t a -> s where
- labelOptic :: Optic k NoIx s t a b
- type LabelOptic' name k s a = LabelOptic name k s s a a
- class GeneralLabelOptic (name :: Symbol) k s t a b (repDefined :: RepDefined) where
- generalLabelOptic :: Optic k NoIx s t a b
- module Optics.Internal.Optic.Subtyping
- module Optics.Internal.Optic.Types
- module Optics.Internal.Optic.TypeLevel
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.
Optic | |
|
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.
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.
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 #
(%) :: (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"]
Labels
class LabelOptic (name :: Symbol) k s t a b | name s -> k a, name t -> k b, name s b -> t, name t a -> s where Source #
Support for overloaded labels as optics. An overloaded label #foo
can be
used as an optic if there is an instance of
.LabelOptic
"foo" k s t a b
See Optics.Label for examples and further details.
labelOptic :: Optic k NoIx s t a b Source #
Used to interpret overloaded label syntax. An overloaded label #foo
corresponds to
.labelOptic
@"foo"
Instances
(LabelOptic name k s t a b, GeneralLabelOptic name k s t a b (AnyHasRep (Rep s) (Rep t))) => LabelOptic name k s t a b Source # | If no instance matches, fall back on |
Defined in Optics.Internal.Optic labelOptic :: Optic k NoIx s t a b Source # |
type LabelOptic' name k s a = LabelOptic name k s s a a Source #
Type synonym for a type-preserving optic as overloaded label.
class GeneralLabelOptic (name :: Symbol) k s t a b (repDefined :: RepDefined) where Source #
Implements fallback behaviour in case there is no explicit LabelOptic
instance. This has a catch-all incoherent instance that merely yields an
error message. However, a downstream module can give a more specific
instance that uses Generic
to construct an optic automatically.
To support this, the last parameter will be instantiated to RepDefined
if
at least one of s
or t
has a Generic
instance.
generalLabelOptic :: Optic k NoIx s t a b Source #
Used to interpret overloaded label syntax in the absence of an explicit
LabelOptic
instance.
Instances
(TypeError ((((((((((((Text "No instance for LabelOptic " :<>: ShowType name) :<>: Text " ") :<>: QuoteType k) :<>: Text " ") :<>: QuoteType s) :<>: Text " ") :<>: QuoteType t) :<>: Text " ") :<>: QuoteType a) :<>: Text " ") :<>: QuoteType b) :$$: Text " (maybe you forgot to define it or misspelled a name?)") :: Constraint) => GeneralLabelOptic name k s t a b repDefined Source # | If no instance matches, GHC tends to bury error messages "No instance for LabelOptic..." within a ton of other error messages about ambiguous type variables and overlapping instances which are irrelevant and confusing. Use incoherent instance providing a custom type error to cut its efforts short. |
Defined in Optics.Internal.Optic generalLabelOptic :: Optic k NoIx s t a b Source # |
Re-exports
module Optics.Internal.Optic.Types