Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- rep :: (Generic a, Generic b) => Iso a b (Rep a) (Rep b)
- productRep :: (IsProductType a xs, IsProductType b ys) => Iso a b (NP I xs) (NP I ys)
- sop :: forall k (f :: k -> Type) xss yss. Iso (SOP f xss) (SOP f yss) (NS (NP f) xss) (NS (NP f) yss)
- pop :: forall k (f :: k -> Type) xss yss. Iso (POP f xss) (POP f yss) (NP (NP f) xss) (NP (NP f) yss)
- _SOP :: forall k (f :: k -> Type) xss yss. Iso (SOP f xss) (SOP f yss) (NS (NP f) xss) (NS (NP f) yss)
- _POP :: forall k (f :: k -> Type) xss yss. Iso (POP f xss) (POP f yss) (NP (NP f) xss) (NP (NP f) yss)
- _I :: Iso (I a) (I b) a b
- _K :: Iso (K a c) (K b c) a b
- npSingleton :: forall k (f :: k -> Type) x y. Iso (NP f '[x]) (NP f '[y]) (f x) (f y)
- npHead :: forall k (f :: k -> Type) x y zs. Lens (NP f (x ': zs)) (NP f (y ': zs)) (f x) (f y)
- npTail :: forall k (f :: k -> Type) x ys zs. Lens (NP f (x ': ys)) (NP f (x ': zs)) (NP f ys) (NP f zs)
- nsSingleton :: forall k (f :: k -> Type) x y. Iso (NS f '[x]) (NS f '[y]) (f x) (f y)
- _Z :: forall k (f :: k -> Type) x y zs. Prism (NS f (x ': zs)) (NS f (y ': zs)) (f x) (f y)
- _S :: forall k (f :: k -> Type) x ys zs. Prism (NS f (x ': ys)) (NS f (x ': zs)) (NS f ys) (NS f zs)
- moduleName :: Lens' (DatatypeInfo xss) ModuleName
- datatypeName :: Lens' (DatatypeInfo xss) DatatypeName
- constructorInfo :: Lens' (DatatypeInfo xss) (NP ConstructorInfo xss)
- constructorName :: Lens' (ConstructorInfo xs) ConstructorName
- strictnessInfo :: Traversal' (DatatypeInfo xss) (POP StrictnessInfo xss)
Representations
rep :: (Generic a, Generic b) => Iso a b (Rep a) (Rep b) Source #
Convert from the data type to its representation (or back).
>>>
Just 'x' ^. rep
SOP (S (Z (I 'x' :* Nil)))
productRep :: (IsProductType a xs, IsProductType b ys) => Iso a b (NP I xs) (NP I ys) Source #
Convert from the product data type to its representation (or back)
>>>
('x', True) ^. productRep
I 'x' :* I True :* Nil
SOP & POP
sop :: forall k (f :: k -> Type) xss yss. Iso (SOP f xss) (SOP f yss) (NS (NP f) xss) (NS (NP f) yss) Source #
The only field of SOP
.
>>>
Just 'x' ^. rep . sop
S (Z (I 'x' :* Nil))
pop :: forall k (f :: k -> Type) xss yss. Iso (POP f xss) (POP f yss) (NP (NP f) xss) (NP (NP f) yss) Source #
The only field of POP
.
_SOP :: forall k (f :: k -> Type) xss yss. Iso (SOP f xss) (SOP f yss) (NS (NP f) xss) (NS (NP f) yss) Source #
Alias for sop
.
_POP :: forall k (f :: k -> Type) xss yss. Iso (POP f xss) (POP f yss) (NP (NP f) xss) (NP (NP f) yss) Source #
Alias for pop
.
Functors
Products
npHead :: forall k (f :: k -> Type) x y zs. Lens (NP f (x ': zs)) (NP f (y ': zs)) (f x) (f y) Source #
npTail :: forall k (f :: k -> Type) x ys zs. Lens (NP f (x ': ys)) (NP f (x ': zs)) (NP f ys) (NP f zs) Source #
Sums
_Z :: forall k (f :: k -> Type) x y zs. Prism (NS f (x ': zs)) (NS f (y ': zs)) (f x) (f y) Source #
_S :: forall k (f :: k -> Type) x ys zs. Prism (NS f (x ': ys)) (NS f (x ': zs)) (NS f ys) (NS f zs) Source #
DatatypeInfo
moduleName :: Lens' (DatatypeInfo xss) ModuleName Source #
datatypeName :: Lens' (DatatypeInfo xss) DatatypeName Source #
constructorInfo :: Lens' (DatatypeInfo xss) (NP ConstructorInfo xss) Source #
constructorName :: Lens' (ConstructorInfo xs) ConstructorName Source #
Note: Infix
constructor has operator as a ConstructorName
. Use as
setter with care.
strictnessInfo :: Traversal' (DatatypeInfo xss) (POP StrictnessInfo xss) Source #
Strictness info is only aviable for ADT
data. This combinator is available only with generics-sop
0.5 or later.
Orphan instances
Wrapped (I a) Source # | |
t ~ I a => Rewrapped (I a) t Source # | |
Wrapped (K a b) Source # | |
Wrapped (POP f xss) Source # | |
Wrapped (SOP f xss) Source # | |
xs ~ (x ': ([] :: [k])) => Wrapped (NS f xs) Source # | |
t ~ K a b => Rewrapped (K a b) t Source # | |
t ~ POP f xss => Rewrapped (POP f xss) t Source # | |
t ~ SOP f xss => Rewrapped (SOP f xss) t Source # | |
(t ~ NS f xs, xs ~ (x ': ([] :: [k]))) => Rewrapped (NS f xs) t Source # | |
Field1 (NP f (x ': zs)) (NP f (y ': zs)) (f x) (f y) Source # | |
Field2 (NP f (a2 ': (x ': zs))) (NP f (a2 ': (y ': zs))) (f x) (f y) Source # | |
Field3 (NP f (a2 ': (b ': (x ': zs)))) (NP f (a2 ': (b ': (y ': zs)))) (f x) (f y) Source # | |
Field4 (NP f (a2 ': (b ': (c ': (x ': zs))))) (NP f (a2 ': (b ': (c ': (y ': zs))))) (f x) (f y) Source # | |
Field5 (NP f (a2 ': (b ': (c ': (d ': (x ': zs)))))) (NP f (a2 ': (b ': (c ': (d ': (y ': zs)))))) (f x) (f y) Source # | |
Field6 (NP f (a2 ': (b ': (c ': (d ': (e ': (x ': zs))))))) (NP f (a2 ': (b ': (c ': (d ': (e ': (y ': zs))))))) (f x) (f y) Source # | |
Field7 (NP f' (a2 ': (b ': (c ': (d ': (e ': (f ': (x ': zs)))))))) (NP f' (a2 ': (b ': (c ': (d ': (e ': (f ': (y ': zs)))))))) (f' x) (f' y) Source # | |
Field8 (NP f' (a2 ': (b ': (c ': (d ': (e ': (f ': (g ': (x ': zs))))))))) (NP f' (a2 ': (b ': (c ': (d ': (e ': (f ': (g ': (y ': zs))))))))) (f' x) (f' y) Source # | |
Field9 (NP f' (a2 ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (x ': zs)))))))))) (NP f' (a2 ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (y ': zs)))))))))) (f' x) (f' y) Source # | |
Field1 (POP f (x ': zs)) (POP f (y ': zs)) (NP f x) (NP f y) Source # | |
Field2 (POP f (a ': (x ': zs))) (POP f (a ': (y ': zs))) (NP f x) (NP f y) Source # | |
Field3 (POP f (a ': (b ': (x ': zs)))) (POP f (a ': (b ': (y ': zs)))) (NP f x) (NP f y) Source # | |
Field4 (POP f (a ': (b ': (c ': (x ': zs))))) (POP f (a ': (b ': (c ': (y ': zs))))) (NP f x) (NP f y) Source # | |
Field5 (POP f (a ': (b ': (c ': (d ': (x ': zs)))))) (POP f (a ': (b ': (c ': (d ': (y ': zs)))))) (NP f x) (NP f y) Source # | |
Field6 (POP f (a ': (b ': (c ': (d ': (e ': (x ': zs))))))) (POP f (a ': (b ': (c ': (d ': (e ': (y ': zs))))))) (NP f x) (NP f y) Source # | |
Field7 (POP f' (a ': (b ': (c ': (d ': (e ': (f ': (x ': zs)))))))) (POP f' (a ': (b ': (c ': (d ': (e ': (f ': (y ': zs)))))))) (NP f' x) (NP f' y) Source # | |
Field8 (POP f' (a ': (b ': (c ': (d ': (e ': (f ': (g ': (x ': zs))))))))) (POP f' (a ': (b ': (c ': (d ': (e ': (f ': (g ': (y ': zs))))))))) (NP f' x) (NP f' y) Source # | |
Field9 (POP f' (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (x ': zs)))))))))) (POP f' (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (y ': zs)))))))))) (NP f' x) (NP f' y) Source # | |