Safe Haskell | None |
---|---|
Language | GHC2021 |
Strongweak.Generic
Description
Generic strengthen
and weaken
.
Synopsis
- weakenGeneric :: (Generic s, Generic w, GWeaken (Rep s) (Rep w)) => s -> w
- strengthenGeneric :: (Generic w, Generic s, GStrengthenD (Rep w) (Rep s)) => w -> Either StrengthenFailure' s
- newtype GenericallySW s w = GenericallySW {
- unGenericallySW :: s
- newtype GenericallySW0 (f :: Strength -> Type) = GenericallySW0 {
- unGenericallySW0 :: f 'Strong
Generic derivation compatibility
The Strengthen
and Weaken
generic derivers allow you to derive instances
between any compatible pair of types. Compatibility is defined as follows:
- Both types' generic representation (the SOP tree structure) match exactly.
- For each leaf pair of types, either the types are identical, or the appropriate instance exists to transform from source to target.
If they aren't compatible, the derivation will fail with a type error.
I don't think GHC strongly guarantees the SOP property, so if you receive
surprising derivation errors, the types might have differing generic
representation structure, even if their flattened representations are identical.
If you experience this let me know, since in my experience GHC's stock Generic
derivation is highly deterministic.
Also, generic strengthening requires that all metadata is present for both types: for the datatype, constructors and selectors. GHC will always add this metadata for you, but manually-derived Generic instances (which are usually a bad idea) do not require it.
Note that the generics only handle one "layer" at a time. If you have a data
type with nested SW
uses, these generics will fail with
a type error. Either use WeakenN
, or write the instances
manually.
Generic derivers
weakenGeneric :: (Generic s, Generic w, GWeaken (Rep s) (Rep w)) => s -> w Source #
Weaken a value generically.
The weak and strong types must be compatible. See Generic
for
the definition of compatibility in this context.
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.
Generic deriving via wrappers
newtype GenericallySW s w Source #
DerivingVia
wrapper for strongweak instances.
We can't use Generically
conveniently because we need to talk about two data
types, not one -- we would have to do something like
, which is ugly. So we instead define our own adorable little "via type"
here!Generically
(Tagged
w
s)
Use like so:
data XYZ (s :: Strength) = XYZ { xyz1 :: SW s Word8 , xyz2 :: Word8 , xyz3 :: () } deriving stock Generic deriving via (GenericallySW (XYZ 'Strong) (XYZ 'Weak)) instance Weaken (XYZ 'Strong) deriving via (GenericallySW (XYZ 'Strong) (XYZ 'Weak)) instance Strengthen (XYZ 'Strong)
Regrettably, use of this requires UndecidableInstances.
Constructors
GenericallySW | |
Fields
|
Instances
(Generic s, Generic w, GStrengthenD (Rep w) (Rep s), Weaken (GenericallySW s w)) => Strengthen (GenericallySW s w) Source # | |||||
Defined in Strongweak.Generic Methods strengthen :: Weakened (GenericallySW s w) -> Either StrengthenFailure' (GenericallySW s w) Source # | |||||
(Generic s, Generic w, GWeaken (Rep s) (Rep w)) => Weaken (GenericallySW s w) Source # | |||||
Defined in Strongweak.Generic Associated Types
Methods weaken :: GenericallySW s w -> Weakened (GenericallySW s w) Source # | |||||
type Weakened (GenericallySW s w) Source # | |||||
Defined in Strongweak.Generic |
newtype GenericallySW0 (f :: Strength -> Type) Source #
GenericallySW
where the type takes a Strength
in its last type var.
Shorter instances for types of a certain shape.
Regrettably, use of this requires UndecidableInstances.
Constructors
GenericallySW0 | |
Fields
|
Instances
(Generic (f 'Strong), Generic (f 'Weak), GStrengthenD (Rep (f 'Weak)) (Rep (f 'Strong)), Weaken (GenericallySW0 f)) => Strengthen (GenericallySW0 f) Source # | |||||
Defined in Strongweak.Generic Methods strengthen :: Weakened (GenericallySW0 f) -> Either StrengthenFailure' (GenericallySW0 f) Source # | |||||
(Generic (f 'Strong), Generic (f 'Weak), GWeaken (Rep (f 'Strong)) (Rep (f 'Weak))) => Weaken (GenericallySW0 f) Source # | |||||
Defined in Strongweak.Generic Associated Types
Methods weaken :: GenericallySW0 f -> Weakened (GenericallySW0 f) Source # | |||||
type Weakened (GenericallySW0 f) Source # | |||||
Defined in Strongweak.Generic |