strongweak-0.4.1: Convert between strong and weak representations of types
Safe HaskellSafe-Inferred
LanguageGHC2021

Strongweak.Generic.Strengthen

Description

strengthen over generic representations.

Strengthen failures are annotated with precise information describing where the failure occurred: datatype name, constructor name, field index (and name if present). To achieve this, we split the generic derivation into 3 classes, each handling/"unwrapping" a different layer of the generic representation: datatype (D), constructor (C) and selector (S).

Synopsis

Documentation

strengthenGeneric :: (Generic w, Generic s, GStrengthenD (Rep w) (Rep s)) => w -> Validation (NonEmpty StrengthenFail) s Source #

Strengthen a value generically.

The weak and strong types must be compatible. See Generic for the definition of compatibility in this context.

class GStrengthenD w s where Source #

Generic strengthening at the datatype level.

Instances

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

Enter a datatype, stripping its metadata wrapper.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenD :: forall (p :: k0). D1 dw w p -> Validation (NonEmpty StrengthenFail) (D1 ds s p) Source #

class GStrengthenC w s where Source #

Generic strengthening at the constructor sum level.

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 StrengthenFail) (V1 p) Source #

(GStrengthenC lw ls, GStrengthenC rw rs) => GStrengthenC (lw :+: rw :: k -> Type) (ls :+: rs :: k -> Type) Source #

Strengthen sum types by casing and strengthening left or right.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenC :: forall (p :: k0). String -> String -> (lw :+: rw) p -> Validation (NonEmpty StrengthenFail) ((ls :+: rs) p) Source #

(GStrengthenS w s, Constructor cw, Constructor cs) => GStrengthenC (C1 cw w :: k -> Type) (C1 cs s :: k -> Type) Source #

Enter a constructor, stripping its metadata wrapper.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenC :: forall (p :: k0). String -> String -> C1 cw w p -> Validation (NonEmpty StrengthenFail) (C1 cs s p) Source #

class GStrengthenS w s where Source #

Generic strengthening at the selector product level.

In order to calculate field indices, we return the current field index alongside the result. This way, the product case can strengthen the left branch, then increment the returned field index and use it for strengthening the right branch.

Methods

gstrengthenS Source #

Arguments

:: String

weak datatype name

-> String

strong datatype name

-> String

weak constructor name

-> String

strong constructor name

-> Natural

current field index (0, from left)

-> w p 
-> (Natural, Validation (NonEmpty StrengthenFail) (s p)) 

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 -> Natural -> U1 p -> (Natural, Validation (NonEmpty StrengthenFail) (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) in order to pass the field index along.

Instance details

Defined in Strongweak.Generic.Strengthen

Methods

gstrengthenS :: forall (p :: k0). String -> String -> String -> String -> Natural -> (lw :*: rw) p -> (Natural, Validation (NonEmpty StrengthenFail) ((ls :*: rs) p)) Source #

(Strengthen s, Weak s ~ w, 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 -> Natural -> S1 mw (Rec0 w) p -> (Natural, Validation (NonEmpty StrengthenFail) (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 -> Natural -> S1 mw (Rec0 w) p -> (Natural, Validation (NonEmpty StrengthenFail) (S1 ms (Rec0 w) p)) Source #

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 #

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 #

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