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

Strongweak.Strengthen

Synopsis

Strengthen class

class Weaken a => Strengthen a where Source #

Attempt to strengthen some Weak a, asserting certain invariants.

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 :: Weak a -> Result a Source #

Attempt to strengthen some Weak a to its associated strong type a.

Instances

Instances details
Strengthen Int16 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Int32 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Int64 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Int8 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Word16 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Word32 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Word64 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen Word8 Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen (Identity a) Source #

Add wrapper.

Instance details

Defined in Strongweak.Strengthen

Typeable a => Strengthen (NonEmpty a) Source #

Strengthen a plain list into a non-empty list by asserting non-emptiness.

Instance details

Defined in Strongweak.Strengthen

Strengthen a => Strengthen [a] Source #

Decomposer. Strengthen every element in a list.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak [a] -> Result [a] Source #

(Strengthen a, Strengthen b) => Strengthen (Either a b) Source #

Decomposer. Strengthen either side of an Either.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak (Either a b) -> Result (Either a b) Source #

(Generic s, Generic w, GStrengthenD (Rep w) (Rep s), Weaken (GenericallySW s w)) => Strengthen (GenericallySW s w) Source # 
Instance details

Defined in Strongweak.Generic.Via

(Strengthen a, Strengthen b) => Strengthen (a, b) Source #

Decomposer. Strengthen both elements of a tuple.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak (a, b) -> Result (a, b) Source #

Strengthen (Const a b) Source #

Add wrapper.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak (Const a b) -> Result (Const a b) Source #

(Predicate p a, Typeable a) => Strengthen (Refined p a) Source #

Assert a predicate to refine a type.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak (Refined p a) -> Result (Refined p a) Source #

(Vector v a, KnownNat n, Typeable v, Typeable a) => Strengthen (Vector v n a) Source #

Strengthen a plain list into a sized vector by asserting length.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak (Vector v n a) -> Result (Vector v n a) Source #

(Predicate1 p f, Typeable f, Typeable a, Typeable ak) => Strengthen (Refined1 p f a) Source #

Assert a functor predicate to refine a type.

Instance details

Defined in Strongweak.Strengthen

Methods

strengthen :: Weak (Refined1 p f a) -> Result (Refined1 p f a) Source #

restrengthen :: (Strengthen a, Weaken a) => a -> Result 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]
Failure ...

Helpers

strengthenBounded :: forall m n. (Typeable n, Integral n, Show n, Typeable m, Integral m, Show m, Bounded m) => n -> Result m Source #

Strengthen one numeric type into another.

n must be "wider" than m.

Strengthen failures

data Fail Source #

A failure encountered during strengthening.

Constructors

FailShow

A failure containing lots of detail. Use in concrete instances where you already have the Shows and Typeables needed.

Fields

FailOther

A failure. Use in abstract instances to avoid heavy contexts. (Remember that generic strengtheners should wrap these nicely anyway!)

Fields

  • [Text]

    failure description

FailField

Some failures occurred when strengthening from one data type to another.

Field indices are from 0 in the respective constructor. Field names are provided if are present in the type.

This is primarily intended to be used by generic strengtheners.

Fields

Instances

Instances details
Show Fail Source # 
Instance details

Defined in Strongweak.Strengthen

Methods

showsPrec :: Int -> Fail -> ShowS #

show :: Fail -> String #

showList :: [Fail] -> ShowS #

Pretty Fail Source # 
Instance details

Defined in Strongweak.Strengthen

Methods

pretty :: Fail -> Doc ann #

prettyList :: [Fail] -> Doc ann #

Helpers

failShow :: forall s w. (Typeable w, Show w, Typeable s) => w -> [Text] -> Result s Source #

maybeFailShow :: forall a. (Typeable (Weak a), Typeable a) => [Text] -> Maybe a -> Result a Source #

Succeed on Just, fail with given detail on Nothing.

Re-exports

type family Weak a :: Type Source #

The weakened type for some type.

Instances

Instances details
type Weak Int16 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Int32 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Int64 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Int8 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Word16 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Word32 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Word64 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak Word8 Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Identity a) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Identity a) = a
type Weak (NonEmpty a) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (NonEmpty a) = [a]
type Weak [a] Source # 
Instance details

Defined in Strongweak.Weaken

type Weak [a] = [Weak a]
type Weak (Either a b) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Either a b) = Either (Weak a) (Weak b)
type Weak (GenericallySW s w) Source # 
Instance details

Defined in Strongweak.Generic.Via

type Weak (GenericallySW s w) = w
type Weak (a, b) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (a, b) = (Weak a, Weak b)
type Weak (Const a b) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Const a b) = a
type Weak (Refined p a) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Refined p a) = a
type Weak (Vector v n a) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Vector v n a) = [a]
type Weak (Refined1 p f a) Source # 
Instance details

Defined in Strongweak.Weaken

type Weak (Refined1 p f a) = f a