| Copyright | (C) 2020 Csongor Kiss | 
|---|---|
| License | BSD3 | 
| Maintainer | Csongor Kiss <kiss.csongor.kiss@gmail.com> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Generics.Sum.Internal.Constructors
Description
Derive constructor-name-based prisms generically.
Synopsis
- class GAsConstructor (ctor :: Symbol) s t a b | ctor s -> a, ctor t -> b where
- type GAsConstructor' ctor s a = GAsConstructor ctor s s a a
- type Context' ctor s a = (Context0 ctor s s a a, ErrorUnless ctor s (HasCtorP ctor (Rep s)))
- class Context (ctor :: Symbol) s t a b | ctor s -> a, ctor t -> b
- class Context_ (ctor :: Symbol) s t a b
- type Context0 ctor s t a b = (Generic s, Generic t, GAsConstructor ctor (Rep s) (Rep t) a b, Defined (Rep s) (NoGeneric s '[(('Text "arising from a generic prism focusing on the " :<>: QuoteType ctor) :<>: 'Text " constructor of type ") :<>: QuoteType a, 'Text "in " :<>: QuoteType s]) (() :: Constraint))
- derived0 :: forall ctor s t a b. Context0 ctor s t a b => Prism s t a b
Documentation
class GAsConstructor (ctor :: Symbol) s t a b | ctor s -> a, ctor t -> b where Source #
As AsConstructor but over generic representations as defined by
  GHC.Generics.
Instances
| GSumAsConstructor ctor (HasCtorP ctor l) l r l' r' a b => GAsConstructor ctor (l :+: r) (l' :+: r') a b Source # | |
| GAsConstructor ctor f f' a b => GAsConstructor ctor (M1 D meta f) (M1 D meta f') a b Source # | |
| (GIsList f g as bs, ListTuple a b as bs) => GAsConstructor ctor (M1 C ('MetaCons ctor fixity fields) f) (M1 C ('MetaCons ctor fixity fields) g) a b Source # | |
type GAsConstructor' ctor s a = GAsConstructor ctor s s a a Source #
type Context' ctor s a = (Context0 ctor s s a a, ErrorUnless ctor s (HasCtorP ctor (Rep s))) Source #
class Context (ctor :: Symbol) s t a b | ctor s -> a, ctor t -> b Source #
Instances
| (ErrorUnless ctor s (HasCtorP ctor (Rep s)), GAsConstructor' ctor (Rep s) a, GAsConstructor' ctor (Rep (Indexed s)) a', GAsConstructor ctor (Rep s) (Rep t) a b, t ~ Infer s a' b, GAsConstructor' ctor (Rep (Indexed t)) b', s ~ Infer t b' a) => Context ctor s t a b Source # | |
| Defined in Data.Generics.Sum.Internal.Constructors | |
class Context_ (ctor :: Symbol) s t a b Source #
Instances
| (ErrorUnless ctor s (HasCtorP ctor (Rep s)), GAsConstructor' ctor (Rep s) a, GAsConstructor' ctor (Rep (Indexed s)) a', GAsConstructor ctor (Rep s) (Rep t) a b, GAsConstructor' ctor (Rep (Indexed t)) b', UnifyHead s t, UnifyHead t s) => Context_ ctor s t a b Source # | |
| Defined in Data.Generics.Sum.Internal.Constructors | |
type Context0 ctor s t a b = (Generic s, Generic t, GAsConstructor ctor (Rep s) (Rep t) a b, Defined (Rep s) (NoGeneric s '[(('Text "arising from a generic prism focusing on the " :<>: QuoteType ctor) :<>: 'Text " constructor of type ") :<>: QuoteType a, 'Text "in " :<>: QuoteType s]) (() :: Constraint)) Source #