Safe Haskell | None |
---|---|
Language | GHC2021 |
Strongweak
Description
Main import module for basic use.
For defining Strengthen
instances, import Strongweak.Strengthen.
Synopsis
- class Weaken a where
- weakenN :: WeakenN n a => a -> WeakenedN n a
- class Weaken a => Strengthen a where
- strengthen :: Weakened a -> Either StrengthenFailure' a
- strengthenN :: StrengthenN n a => WeakenedN n a -> Either StrengthenFailure' a
- newtype SWChain (n :: Natural) a = SWChain {
- unSWChain :: a
- newtype SWCoercibly a = SWCoercibly {
- unSWCoercibly :: a
- liftWeakF :: Weaken a => (Weakened a -> b) -> a -> b
- data Strength
- type family SW (s :: Strength) a where ...
Instance design
A given strong type a
has exactly one associated weak type
.
Multiple strong types may weaken to the same weak type.Weakened
a
The following laws must hold:
weaken
a ==weaken
b |= a == bstrengthen
(weaken
a) ==pure
a
strongweak is largely a programmer convenience library. There is a lot of room to write instances which may seem useful on first glance, but are inconsistent with the overall design. Here is some relevant guidance.
- Weak types should have _simpler invariants to manage_ than strong ones.
- In general, weak types should be easier to use than strong ones.
- Most (all?) instances should handle (relax or assert) a single invariant.
- Most instances should not have a recursive context.
If you want to handle multiple invariants, chain the weakens/strengthens.
You may do this by nesting SW
uses, but you will then have to write your own
instances, as the generics cannot handle such chaining. Alternatively, you may
use WeakenN
. This will add another newtype layer to the strong representation,
but the generics are happy with it.
Some types may not have any invariants which may be usefully relaxed e.g.
. For these, you may write a recursive instance that
weakens/strengthens "through" the type e.g. Either
a b(
). Don't combine the two instance types.Weak
a, Weak
b) => Weak
(Either
a b)
An example is
. We could weaken this to NonEmpty
a[a]
,
but also to [
. However, the latter would mean decomposing and
removing an invariant simultaneously. It would be two separate strengthens in
one instance. And now, your Weak
a]a
must be in the strongweak ecosystem, which isn't
necessarily what you want - indeed, it appears this sort of design would require
a
overlapping instance, which I do not want. On the
other hand, Weak
a = a, weaken = id[a]
does weaken to [
, because there are no invariants
present to remove, so decomposing is all the user could hope to do.Weak
a]
Classes
Weaken some a
, relaxing certain invariants.
See Strongweak for class design notes and laws.
Instances
class Weaken a => Strengthen a where Source #
Attempt to strengthen some
, asserting certain invariants.Weakened
a
We take Weaken
as a superclass in order to maintain strong/weak type pair
consistency. We choose this dependency direction because we treat the strong
type as the "canonical" one, so Weaken
is the more natural (and
straightforward) class to define. That does mean the instances for this class
are a little confusingly worded. Alas.
See Strongweak for class design notes and laws.
Methods
strengthen :: Weakened a -> Either StrengthenFailure' a Source #
Attempt to strengthen some
to its associated strong type
Weakened
aa
.
Instances
Strengthen Int16 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Int16 -> Either StrengthenFailure' Int16 Source # | |
Strengthen Int32 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Int32 -> Either StrengthenFailure' Int32 Source # | |
Strengthen Int64 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Int64 -> Either StrengthenFailure' Int64 Source # | |
Strengthen Int8 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Int8 -> Either StrengthenFailure' Int8 Source # | |
Strengthen Word16 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Word16 -> Either StrengthenFailure' Word16 Source # | |
Strengthen Word32 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Word32 -> Either StrengthenFailure' Word32 Source # | |
Strengthen Word64 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Word64 -> Either StrengthenFailure' Word64 Source # | |
Strengthen Word8 Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened Word8 -> Either StrengthenFailure' Word8 Source # | |
Strengthen (Identity a) Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (Identity a) -> Either StrengthenFailure' (Identity a) Source # | |
Strengthen (NonEmpty a) Source # | Strengthen a plain list into a non-empty list by asserting non-emptiness. |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (NonEmpty a) -> Either StrengthenFailure' (NonEmpty a) Source # | |
(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 # | |
Strengthen (SWCoercibly a) Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (SWCoercibly a) -> Either StrengthenFailure' (SWCoercibly a) Source # | |
Strengthen a => Strengthen [a] Source # | Decomposer. Strengthen every element in a list. |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened [a] -> Either StrengthenFailure' [a] Source # | |
(Strengthen a, Strengthen b) => Strengthen (Either a b) Source # | Decomposer. Strengthen either side of an |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (Either a b) -> Either StrengthenFailure' (Either a b) Source # | |
StrengthenN n a => Strengthen (SWChain n a) Source # | |
Defined in Strongweak.Chain Methods strengthen :: Weakened (SWChain n a) -> Either StrengthenFailure' (SWChain n a) Source # | |
(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 # | |
(Strengthen l, Strengthen r) => Strengthen (l, r) Source # | Decomposer. Strengthen both elements of a tuple. |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (l, r) -> Either StrengthenFailure' (l, r) Source # | |
Strengthen (Const a b) Source # | |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (Const a b) -> Either StrengthenFailure' (Const a b) Source # | |
Refine p a => Strengthen (Refined p a) Source # | Strengthen a type by refining it with a predicate. |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (Refined p a) -> Either StrengthenFailure' (Refined p a) Source # | |
(Vector v a, KnownNat n) => Strengthen (Vector v n a) Source # | Strengthen a plain list into a sized vector by asserting length. |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (Vector v n a) -> Either StrengthenFailure' (Vector v n a) Source # | |
Refine1 p f => Strengthen (Refined1 p f a) Source # | Strengthen a type by refining it with a functor predicate. |
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (Refined1 p f a) -> Either StrengthenFailure' (Refined1 p f a) Source # |
strengthenN :: StrengthenN n a => WeakenedN n a -> Either StrengthenFailure' a Source #
Other definitions
newtype SWChain (n :: Natural) a Source #
When weakening (or strengthening), chain the operation n
times.
You may achieve this without extra newtypes by nesting uses of
SW
. However, strongweak generics can't handle this,
forcing you to write manual instances.
SWChain
provides this nesting behaviour in a type. In return for adding a
boring newtype layer to the strong representation, you can chain weakening and
strengthenings without having to write them manually.
The type works as follows:
Weakened
(SWChain
0 a) = aWeakened
(SWChain
1 a) =Weakened
aWeakened
(SWChain
2 a) =Weakened
(Weakened
a)Weakened
(SWChain
n a) =WeakenedN
n a
And so on. (This type is only much use from n = 2
onwards.)
You may also use this as a "via" type:
newtype A (s ::Strength
) = A { a1 ::SW
s (Identity (SW
s Word8)) } deriving viaSWChain
2 (Identity Word8) instanceWeaken
(AStrong
) deriving viaSWChain
2 (Identity Word8) instanceStrengthen
(AStrong
)
Instances
Show a => Show (SWChain n a) Source # | |
Eq a => Eq (SWChain n a) Source # | |
Ord a => Ord (SWChain n a) Source # | |
Defined in Strongweak.Chain | |
StrengthenN n a => Strengthen (SWChain n a) Source # | |
Defined in Strongweak.Chain Methods strengthen :: Weakened (SWChain n a) -> Either StrengthenFailure' (SWChain n a) Source # | |
WeakenN n a => Weaken (SWChain n a) Source # | |
type Weakened (SWChain n a) Source # | |
Defined in Strongweak.Chain |
newtype SWCoercibly a Source #
A "via type" newtype for defining strongweak instances for zero-invariant, coercible newtypes.
Use like so:
derivingWeaken
viaSWCoercibly
a
Or standalone:
viaSWCoercibly
a instanceWeaken
(Identity
a)
Note that usage of this incurs UndecidableInstances. That's life. You can write the trivial instances this generates yourself if you so wish.
Constructors
SWCoercibly | |
Fields
|
Instances
Strengthen (SWCoercibly a) Source # | |||||
Defined in Strongweak.Strengthen Methods strengthen :: Weakened (SWCoercibly a) -> Either StrengthenFailure' (SWCoercibly a) Source # | |||||
UnsafeStrengthen (SWCoercibly a) Source # | |||||
Defined in Strongweak.Strengthen.Unsafe Methods unsafeStrengthen :: Weakened (SWCoercibly a) -> SWCoercibly a Source # | |||||
Weaken (SWCoercibly a) Source # | |||||
Defined in Strongweak.Weaken Associated Types
Methods weaken :: SWCoercibly a -> Weakened (SWCoercibly a) Source # | |||||
type Weakened (SWCoercibly a) Source # | |||||
Defined in Strongweak.Weaken |
liftWeakF :: Weaken a => (Weakened a -> b) -> a -> b Source #
Lift a function on a weak type to the associated strong type by weakening first.
Strength switch wrapper
Strength enumeration: it's either strong, or weak.
Primarily interesting at the type level (using DataKinds).
type family SW (s :: Strength) a where ... Source #
Get either the strong or weak representation of a type, depending on the type-level "switch" provided.
This is intended to be used in data types that take a Strength
type. Define
your type using strong fields wrapped in SW s
. You then get the weak
representation for free, using the same definition.
data A (s :: Strength) = A { a1 :: SW s Word8 , a2 :: String }