Safe Haskell | None |
---|---|
Language | GHC2021 |
Strongweak.Strengthen.Generic
Description
strengthen
over generic representations.
As with base instances, generic strengthening collates all failures rather than short-circuiting on the first failure. Failures are annotated with precise information describing where the failure occurred:
- data type name
- constructor name
- field index
- field name (if present)
Synopsis
- strengthenGeneric :: (Generic w, Generic s, GStrengthenD (Rep w) (Rep s)) => w -> Either StrengthenFailure' s
- class GStrengthenD (w :: k -> Type) (s :: k -> Type) where
- gstrengthenD :: forall (p :: k). w p -> Either StrengthenFailure' (s p)
- class GStrengthenC (wdn :: Symbol) (sdn :: Symbol) (w :: k -> Type) (s :: k -> Type) where
- gstrengthenC :: forall (p :: k). w p -> Either StrengthenFailure' (s p)
- class ReifyCstrs (ld :: Symbol) (lc :: Symbol) (rd :: Symbol) (rc :: Symbol) where
- class GStrengthenS (i :: Natural) (w :: k -> Type) (s :: k -> Type) where
- gstrengthenS :: forall (p :: k). w p -> Either [(Builder, StrengthenFailure')] (s p)
- class ReifySelector (i :: Natural) (l :: Maybe Symbol) (r :: Maybe Symbol) where
- (.>) :: (a -> b) -> (b -> c) -> a -> c
- type family ProdArity (f :: k -> Type) :: Natural where ...
Documentation
strengthenGeneric :: (Generic w, Generic s, GStrengthenD (Rep w) (Rep s)) => w -> Either StrengthenFailure' 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 :: k -> Type) (s :: k -> Type) where Source #
Generic strengthening at the datatype level.
Methods
gstrengthenD :: forall (p :: k). w p -> Either StrengthenFailure' (s p) Source #
Instances
GStrengthenC wdn sdn w s => GStrengthenD (D1 ('MetaData wdn _wmd2 _wmd3 _wmd4) w :: k -> Type) (D1 ('MetaData sdn _smd2 _smd3 _smd4) s :: k -> Type) Source # | Strengthen a generic data type, replacing its metadata wrapping. |
Defined in Strongweak.Strengthen.Generic Methods gstrengthenD :: forall (p :: k). D1 ('MetaData wdn _wmd2 _wmd3 _wmd4) w p -> Either StrengthenFailure' (D1 ('MetaData sdn _smd2 _smd3 _smd4) s p) Source # |
class GStrengthenC (wdn :: Symbol) (sdn :: Symbol) (w :: k -> Type) (s :: k -> Type) where Source #
Generic strengthening at the constructor sum level.
Methods
gstrengthenC :: forall (p :: k). w p -> Either StrengthenFailure' (s p) Source #
Instances
GStrengthenC wdn sdn (V1 :: k -> Type) (V1 :: k -> Type) Source # | Nothing to do for empty datatypes. |
Defined in Strongweak.Strengthen.Generic Methods gstrengthenC :: forall (p :: k). V1 p -> Either StrengthenFailure' (V1 p) Source # | |
(GStrengthenS 0 w s, ReifyCstrs wcd wcn scd scn) => GStrengthenC wcd scd (C1 ('MetaCons wcn _wmc2 _wmc3) w :: k -> Type) (C1 ('MetaCons scn _smc2 _smc3) s :: k -> Type) Source # | Enter a constructor, stripping its metadata wrapper. |
Defined in Strongweak.Strengthen.Generic Methods gstrengthenC :: forall (p :: k). C1 ('MetaCons wcn _wmc2 _wmc3) w p -> Either StrengthenFailure' (C1 ('MetaCons scn _smc2 _smc3) s p) Source # | |
(GStrengthenC wdn sdn wl sl, GStrengthenC wdn sdn wr sr) => GStrengthenC wdn sdn (wl :+: wr :: k -> Type) (sl :+: sr :: k -> Type) Source # | Strengthen sum types by casing and strengthening left or right. |
Defined in Strongweak.Strengthen.Generic Methods gstrengthenC :: forall (p :: k). (wl :+: wr) p -> Either StrengthenFailure' ((sl :+: sr) p) Source # |
class ReifyCstrs (ld :: Symbol) (lc :: Symbol) (rd :: Symbol) (rc :: Symbol) where Source #
Methods
reifyCstrs :: Builder Source #
Instances
(KnownSymbol d, KnownSymbol c) => ReifyCstrs d c d c Source # | Special case: data type and constructor names are equivalent: simplify |
Defined in Strongweak.Strengthen.Generic Methods reifyCstrs :: Builder Source # | |
(KnownSymbol ld, KnownSymbol lc, KnownSymbol rd, KnownSymbol rc) => ReifyCstrs ld lc rd rc Source # | |
Defined in Strongweak.Strengthen.Generic Methods reifyCstrs :: Builder Source # |
class GStrengthenS (i :: Natural) (w :: k -> Type) (s :: k -> Type) where Source #
Generic strengthening at the constructor level.
Methods
gstrengthenS :: forall (p :: k). w p -> Either [(Builder, StrengthenFailure')] (s p) Source #
Instances
GStrengthenS i (U1 :: k -> Type) (U1 :: k -> Type) Source # | Nothing to do for empty constructors. |
Defined in Strongweak.Strengthen.Generic Methods gstrengthenS :: forall (p :: k). U1 p -> Either [(Builder, StrengthenFailure')] (U1 p) Source # | |
(GStrengthenS i wl sl, GStrengthenS (i + ProdArity wl) wr sr) => GStrengthenS i (wl :*: wr :: k -> Type) (sl :*: sr :: k -> Type) Source # | Strengthen product types by strengthening left and right. |
Defined in Strongweak.Strengthen.Generic Methods gstrengthenS :: forall (p :: k). (wl :*: wr) p -> Either [(Builder, StrengthenFailure')] ((sl :*: sr) p) Source # | |
GStrengthenS i (S1 ('MetaSel _wms1 _wms2 _wms3 _wms4) (Rec0 a) :: k -> Type) (S1 ('MetaSel _sms1 _sms2 _sms3 _sms4) (Rec0 a) :: k -> Type) Source # | Special case: if source and target types are equivalent, just replace meta. Note that we have to expand the metadata awkwardly for the overlapping instances to work correctly. (There should be a better way to write this, but it's purely style, so light TODO.) |
Defined in Strongweak.Strengthen.Generic | |
(Weakened s ~ w, Strengthen s, ReifySelector i wmr smr) => GStrengthenS i (S1 ('MetaSel wmr _wms2 _wms3 _wms4) (Rec0 w) :: k -> Type) (S1 ('MetaSel smr _sms2 _sms3 _sms4) (Rec0 s) :: k -> Type) Source # | Strengthen a field using the existing |
Defined in Strongweak.Strengthen.Generic |
class ReifySelector (i :: Natural) (l :: Maybe Symbol) (r :: Maybe Symbol) where Source #
Methods
Instances
KnownNat i => ReifySelector i ('Nothing :: Maybe Symbol) ('Nothing :: Maybe Symbol) Source # | |
Defined in Strongweak.Strengthen.Generic Methods | |
(KnownNat i, KnownSymbol rnm) => ReifySelector i ('Nothing :: Maybe Symbol) ('Just rnm) Source # | |
Defined in Strongweak.Strengthen.Generic Methods | |
(KnownNat i, KnownSymbol lnm) => ReifySelector i ('Just lnm) ('Nothing :: Maybe Symbol) Source # | |
Defined in Strongweak.Strengthen.Generic Methods | |
(KnownNat i, KnownSymbol lnm) => ReifySelector i ('Just lnm) ('Just lnm) Source # | Special case: both types had a record name, and they're equal |
Defined in Strongweak.Strengthen.Generic Methods | |
(KnownNat i, KnownSymbol lnm, KnownSymbol rnm) => ReifySelector i ('Just lnm) ('Just rnm) Source # | |
Defined in Strongweak.Strengthen.Generic Methods |