Safe Haskell | None |
---|---|
Language | GHC2021 |
Strongweak.Strengthen
Synopsis
- class Weaken a => Strengthen a where
- strengthen :: Weakened a -> Either StrengthenFailure' a
- restrengthen :: (Strengthen a, Weaken a) => a -> Either StrengthenFailure' a
- class WeakenN n a => StrengthenN (n :: Natural) a where
- strengthenN :: WeakenedN n a -> Either StrengthenFailure' a
- strengthenBounded :: forall m n. (Typeable n, Integral n, Typeable m, Integral m, Bounded m, FiniteBits m) => n -> Either StrengthenFailure' m
- data StrengthenFailure text = StrengthenFailure {
- strengthenFailDetail :: [text]
- strengthenFailInner :: [(text, StrengthenFailure text)]
- type StrengthenFailure' = StrengthenFailure Builder
- failStrengthen1 :: [text] -> Either (StrengthenFailure text) a
- failStrengthen :: [text] -> [(text, StrengthenFailure text)] -> Either (StrengthenFailure text) a
- type family Weakened a
Strengthen
class
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
restrengthen :: (Strengthen a, Weaken a) => a -> Either StrengthenFailure' a Source #
Weaken a strong value, then strengthen it again.
Potentially useful if you have previously used
unsafeStrengthen
and now wish to check the
invariants. For example:
>>>
restrengthen $ unsafeStrengthen @(Vector 2 Natural) [0]
Left ...
class WeakenN n a => StrengthenN (n :: Natural) a where Source #
Methods
strengthenN :: WeakenedN n a -> Either StrengthenFailure' a Source #
Instances
(Strengthen a, StrengthenN (n - 1) (Weakened a)) => StrengthenN n a Source # | |
Defined in Strongweak.Strengthen Methods strengthenN :: WeakenedN n a -> Either StrengthenFailure' a Source # | |
StrengthenN 0 a Source # | |
Defined in Strongweak.Strengthen Methods strengthenN :: WeakenedN 0 a -> Either StrengthenFailure' a Source # |
Helpers
strengthenBounded :: forall m n. (Typeable n, Integral n, Typeable m, Integral m, Bounded m, FiniteBits m) => n -> Either StrengthenFailure' m Source #
Strengthen one numeric type into another.
n
must be "wider" than m
.
is for error printing.FiniteBits
m
Strengthen failures
data StrengthenFailure text Source #
A failure encountered during strengthening.
Strengthening can involve multiple distinct checks. In such cases, you may
record multiple failures in a single StrengthenFailure
by placing them in
the inner failure list and noting their meaning in the detail field.
Constructors
StrengthenFailure | |
Fields
|
Instances
Show text => Show (StrengthenFailure text) Source # | |
Defined in Strongweak.Strengthen Methods showsPrec :: Int -> StrengthenFailure text -> ShowS # show :: StrengthenFailure text -> String # showList :: [StrengthenFailure text] -> ShowS # |
failStrengthen1 :: [text] -> Either (StrengthenFailure text) a Source #
Shorthand for failing a strengthen with no inner failures.
failStrengthen :: [text] -> [(text, StrengthenFailure text)] -> Either (StrengthenFailure text) a Source #
Shorthand for failing a strengthen.
Re-exports
type family Weakened a Source #
The weakened type for some type.