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

Strongweak

Description

Main import module for basic use.

For defining Strengthen instances, import Strongweak.Strengthen.

Synopsis

Instance design

A given strong type a has exactly one associated weak type Weaken a. Multiple strong types may weaken to the same weak type.

The following laws must hold:

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.

Some types may not have any invariants which may be usefully relaxed e.g. Either a b. For these, you may write a recursive instance that weakens/strengthens "through" the type e.g. (Weaken a, Weaken b) => Weak (Either a b)). Don't combine the two instance types.

An example is NonEmpty a. We could weaken this to [a], but also to [Weaken a]. However, the latter would mean decomposing and removing an invariant simultaneously. It would be two separate strengthens in one instance. And now, your a must be in the strongweak ecosystem, which isn't necessarily what you want - indeed, it appears this sort of design would require a Weaken a = a, weaken = id overlapping instance, which I do not want. On the other hand, [a] does weaken to [Weaken a], because there are no invariants present to remove, so decomposing is all the user could hope to do.

Classes

class Weaken a where Source #

Weaken some a, relaxing certain invariants.

See Strongweak for class design notes and laws.

Associated Types

type Weak a :: Type Source #

The weakened type for some type.

Methods

weaken :: a -> Weak a Source #

Weaken some a to its associated weak type Weaken a.

Instances

Instances details
Weaken Int16 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Int16 Source #

Methods

weaken :: Int16 -> Weak Int16 Source #

Weaken Int32 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Int32 Source #

Methods

weaken :: Int32 -> Weak Int32 Source #

Weaken Int64 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Int64 Source #

Methods

weaken :: Int64 -> Weak Int64 Source #

Weaken Int8 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Int8 Source #

Methods

weaken :: Int8 -> Weak Int8 Source #

Weaken Word16 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Word16 Source #

Weaken Word32 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Word32 Source #

Weaken Word64 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Word64 Source #

Weaken Word8 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak Word8 Source #

Methods

weaken :: Word8 -> Weak Word8 Source #

Weaken (Identity a) Source #

Strip wrapper.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Identity a) Source #

Methods

weaken :: Identity a -> Weak (Identity a) Source #

Weaken (NonEmpty a) Source #

Weaken non-empty lists into plain lists.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (NonEmpty a) Source #

Methods

weaken :: NonEmpty a -> Weak (NonEmpty a) Source #

Weaken a => Weaken [a] Source #

Decomposer. Weaken every element in a list.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak [a] Source #

Methods

weaken :: [a] -> Weak [a] Source #

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

Decomposer. Weaken either side of an Either.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Either a b) Source #

Methods

weaken :: Either a b -> Weak (Either a b) Source #

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

Defined in Strongweak.Generic.Via

Associated Types

type Weak (GenericallySW s w) Source #

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

Decomposer. Weaken both elements of a tuple.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (a, b) Source #

Methods

weaken :: (a, b) -> Weak (a, b) Source #

Weaken (Const a b) Source #

Strip wrapper.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Const a b) Source #

Methods

weaken :: Const a b -> Weak (Const a b) Source #

Weaken (Refined p a) Source #

Strip refined type refinement.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Refined p a) Source #

Methods

weaken :: Refined p a -> Weak (Refined p a) Source #

Vector v a => Weaken (Vector v n a) Source #

Weaken sized vectors into plain lists.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Vector v n a) Source #

Methods

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

Weaken (Refined1 p f a) Source #

Strip refined functor type refinement.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Refined1 p f a) Source #

Methods

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

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 #

Other definitions

liftWeakF :: Weaken a => (Weak a -> b) -> a -> b Source #

Lift a function on a weak type to the associated strong type by weakening first.

Strength switch wrapper

data Strength Source #

Strength enumeration: is it strong, or weak?

Primarily interesting at the type level (using DataKinds).

Constructors

Strong 
Weak 

type family SW (s :: Strength) a :: Type 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 }

Equations

SW 'Strong a = a 
SW 'Weak a = Weak a