| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Strongweak.Generic.Strengthen
Description
Strengthening for generic data types.
The generic derivation is split into 3 classes, each dealing with a different layer of a generic Haskell data type: datatype (D), constructor (C) and selector (S). At each point, we gather up information about the type and push on. Strengthening occurs at selectors. If a strengthening fails, the gathered information is pushed into an error that wraps the original error.
Synopsis
- strengthenGeneric :: (Generic w, Generic s, GStrengthenD (Rep w) (Rep s)) => w -> Validation (NonEmpty StrengthenError) s
- class GStrengthenD w s where
- gstrengthenD :: w p -> Validation (NonEmpty StrengthenError) (s p)
- class GStrengthenC w s where
- gstrengthenC :: String -> String -> w p -> Validation (NonEmpty StrengthenError) (s p)
- class GStrengthenS w s where
- gstrengthenS :: String -> String -> String -> String -> Natural -> w p -> (Natural, Validation (NonEmpty StrengthenError) (s p))
- selName'' :: forall s. Selector s => Maybe String
- conName' :: forall c. Constructor c => String
- datatypeName' :: forall d. Datatype d => String
- selName' :: forall s. Selector s => String
Documentation
strengthenGeneric :: (Generic w, Generic s, GStrengthenD (Rep w) (Rep s)) => w -> Validation (NonEmpty StrengthenError) s Source #
class GStrengthenD w s where Source #
Methods
gstrengthenD :: w p -> Validation (NonEmpty StrengthenError) (s p) Source #
Instances
| (GStrengthenC w s, Datatype dw, Datatype ds) => GStrengthenD (D1 dw w :: k -> Type) (D1 ds s :: k -> Type) Source # | |
Defined in Strongweak.Generic.Strengthen Methods gstrengthenD :: forall (p :: k0). D1 dw w p -> Validation (NonEmpty StrengthenError) (D1 ds s p) Source # | |
class GStrengthenC w s where Source #
Methods
gstrengthenC :: String -> String -> w p -> Validation (NonEmpty StrengthenError) (s p) Source #
Instances
| GStrengthenC (V1 :: k -> Type) (V1 :: k -> Type) Source # | Nothing to do for empty datatypes. |
Defined in Strongweak.Generic.Strengthen Methods gstrengthenC :: forall (p :: k0). String -> String -> V1 p -> Validation (NonEmpty StrengthenError) (V1 p) Source # | |
| (GStrengthenC lw ls, GStrengthenC rw rs) => GStrengthenC (lw :+: rw :: k -> Type) (ls :+: rs :: k -> Type) Source # | Strengthen sum types by strengthening left or right. |
Defined in Strongweak.Generic.Strengthen Methods gstrengthenC :: forall (p :: k0). String -> String -> (lw :+: rw) p -> Validation (NonEmpty StrengthenError) ((ls :+: rs) p) Source # | |
| (GStrengthenS w s, Constructor cw, Constructor cs) => GStrengthenC (C1 cw w :: k -> Type) (C1 cs s :: k -> Type) Source # | |
Defined in Strongweak.Generic.Strengthen Methods gstrengthenC :: forall (p :: k0). String -> String -> C1 cw w p -> Validation (NonEmpty StrengthenError) (C1 cs s p) Source # | |
class GStrengthenS w s where Source #
Methods
gstrengthenS :: String -> String -> String -> String -> Natural -> w p -> (Natural, Validation (NonEmpty StrengthenError) (s p)) Source #
Instances
| GStrengthenS (U1 :: k -> Type) (U1 :: k -> Type) Source # | Nothing to do for empty constructors. |
Defined in Strongweak.Generic.Strengthen Methods gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> Natural -> U1 p -> (Natural, Validation (NonEmpty StrengthenError) (U1 p)) Source # | |
| (GStrengthenS lw ls, GStrengthenS rw rs) => GStrengthenS (lw :*: rw :: k -> Type) (ls :*: rs :: k -> Type) Source # | Strengthen product types by strengthening left and right. This is ordered (left then right), but only to pass the index along. |
Defined in Strongweak.Generic.Strengthen Methods gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> Natural -> (lw :*: rw) p -> (Natural, Validation (NonEmpty StrengthenError) ((ls :*: rs) p)) Source # | |
| (Strengthen w s, Selector mw, Selector ms) => GStrengthenS (S1 mw (Rec0 w) :: k -> Type) (S1 ms (Rec0 s) :: k -> Type) Source # | Strengthen a field using the existing On strengthen failure, the errors are annotated with all the datatype
information we've hoarded. The upshot is that if you strengthen a type with
lots of types inside it, all with generically-derived |
Defined in Strongweak.Generic.Strengthen | |
| GStrengthenS (S1 mw (Rec0 w) :: k -> Type) (S1 ms (Rec0 w) :: k -> Type) Source # | Special case: if source and target types are equal, copy the value through. |
Defined in Strongweak.Generic.Strengthen | |
selName'' :: forall s. Selector s => Maybe String Source #
Get the record name for a selector if present.
On the type level, a 'Maybe Symbol' is stored for record names. But the
reification is done using fromMaybe "". So we have to inspect the resulting
string to determine whether the field uses record syntax or not. (Silly.)
conName' :: forall c. Constructor c => String Source #
datatypeName' :: forall d. Datatype d => String Source #
datatypeName without the value (only used as a proxy). Lets us push our
undefineds into one place.