strongweak-0.1.0: Convert between strong and weak representations of types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Strongweak.Generic.Strengthen

Description

The generic derivation is split into 3 classes, dealing with different layers of a Haskell data type: datatype, constructor and selector. 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

Documentation

class GStrengthenD w s where Source #

Instances

Instances details
(GStrengthenC w s, Datatype dw, Datatype ds) => GStrengthenD (D1 dw w :: k -> Type) (D1 ds s :: k -> Type) Source # 
Instance details

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 #

Instances

Instances details
GStrengthenC (V1 :: k -> Type) (V1 :: k -> Type) Source #

Nothing to do for empty datatypes.

Instance details

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.

Instance details

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 # 
Instance details

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 #

Instances

Instances details
GStrengthenS (U1 :: k -> Type) (U1 :: k -> Type) Source #

Nothing to do for empty constructors.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> U1 p -> 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, then right.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> (lw :*: rw) p -> 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 Strengthen instance.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> S1 mw (Rec0 w) p -> Validation (NonEmpty StrengthenError) (S1 ms (Rec0 s) p) Source #

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.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> S1 mw (Rec0 w) p -> Validation (NonEmpty StrengthenError) (S1 ms (Rec0 w) p) Source #

conName' :: forall c. Constructor c => String Source #

conName without the value (only used as a proxy). Lets us push our undefineds into one place.

datatypeName' :: forall d. Datatype d => String Source #

datatypeName without the value (only used as a proxy). Lets us push our undefineds into one place.

selName' :: forall s. Selector s => String Source #

datatypeName without the value (only used as a proxy). Lets us push our undefineds into one place.