Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides instances of LabelOptic
to be
used in conjunction with the optics
package.
In particular, there are two kind of optics to access
different parts of a Term
:
- With
#field
you obtain the lens (that is, a getter and a setter) for the corresponding field in a record. - With
#choice
you obtain the prism for the desired choice in an enumeration. You can use thenreview
to construct a term with the value.
In addition, we provide a utility function record
to
build a record out of the inner values. We intend the
interface to be very simple, so this function is overloaded
to take tuples of different size, with as many components
as values in the schema type.
Synopsis
- record :: BuildRecord sch args r => r -> Term sch ('DRecord name args)
- record1 :: TypeLabel sch t1 r1 => r1 -> Term sch ('DRecord name '['FieldDef x1 t1])
- enum :: forall (choiceName :: Symbol) choices sch name. EnumLabel choices choiceName => Term sch ('DEnum name choices)
- _U0 :: forall (sch :: Schema') x xs r. TypeLabel sch x r => Prism' (NS (FieldValue sch) (x ': xs)) r
- _Next :: forall (sch :: Schema') x xs. Prism' (NS (FieldValue sch) (x ': xs)) (NS (FieldValue sch) xs)
- _U1 :: forall (sch :: Schema') a b xs r. TypeLabel sch b r => Prism' (NS (FieldValue sch) (a ': (b ': xs))) r
- _U2 :: forall (sch :: Schema') a b c xs r. TypeLabel sch c r => Prism' (NS (FieldValue sch) (a ': (b ': (c ': xs)))) r
- _U3 :: forall (sch :: Schema') a b c d xs r. TypeLabel sch d r => Prism' (NS (FieldValue sch) (a ': (b ': (c ': (d ': xs))))) r
- module Optics.Core
- is :: Is k An_AffineFold => s -> Optic' k is s a -> Bool
Build a term
record :: BuildRecord sch args r => r -> Term sch ('DRecord name args) Source #
Build a Mu record Term
from a tuple of its values.
Note: if the record has exactly _one_ field,
you must use record1
instead.
record1 :: TypeLabel sch t1 r1 => r1 -> Term sch ('DRecord name '['FieldDef x1 t1]) Source #
Build a Mu record Term
with exactly one field.
enum :: forall (choiceName :: Symbol) choices sch name. EnumLabel choices choiceName => Term sch ('DEnum name choices) Source #
Build a Mu enumeration Term
from the name of the choice.
_U0 :: forall (sch :: Schema') x xs r. TypeLabel sch x r => Prism' (NS (FieldValue sch) (x ': xs)) r Source #
Prism to access the first choice of a union.
_Next :: forall (sch :: Schema') x xs. Prism' (NS (FieldValue sch) (x ': xs)) (NS (FieldValue sch) xs) Source #
Prism to access all other choices of a union
except for the first. Intended to use be used
iteratively until you reach the desired choice
with _U0
.
_Next % _Next % _U0 -- access third choice
_U1 :: forall (sch :: Schema') a b xs r. TypeLabel sch b r => Prism' (NS (FieldValue sch) (a ': (b ': xs))) r Source #
Prism to access the second choice of a union.
_U2 :: forall (sch :: Schema') a b c xs r. TypeLabel sch c r => Prism' (NS (FieldValue sch) (a ': (b ': (c ': xs)))) r Source #
Prism to access the third choice of a union.
_U3 :: forall (sch :: Schema') a b c d xs r. TypeLabel sch d r => Prism' (NS (FieldValue sch) (a ': (b ': (c ': (d ': xs))))) r Source #
Prism to access the fourth choice of a union.
Re-exported for convenience.
module Optics.Core
Additional utilities.
Orphan instances
(EnumLabel choices choiceName, r ~ ()) => LabelOptic choiceName A_Prism (Term sch ('DEnum name choices :: TypeDefB Type typeName Symbol)) (Term sch ('DEnum name choices :: TypeDefB Type typeName Symbol)) r r Source # | |
labelOptic :: Optic A_Prism NoIx (Term sch ('DEnum name choices)) (Term sch ('DEnum name choices)) r r # | |
FieldLabel sch args fieldName r => LabelOptic fieldName A_Lens (Term sch ('DRecord name args)) (Term sch ('DRecord name args)) r r Source # | |
labelOptic :: Optic A_Lens NoIx (Term sch ('DRecord name args)) (Term sch ('DRecord name args)) r r # |