strongweak
Safe HaskellNone
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 Weakened 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.

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. Either a b. For these, you may write a recursive instance that weakens/strengthens "through" the type e.g. (Weak a, Weak 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 [Weak 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 Weak a = a, weaken = id overlapping instance, which I do not want. On the other hand, [a] does weaken to [Weak 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 Weakened a Source #

The weakened type for some type.

Methods

weaken :: a -> Weakened a Source #

Weaken some a to its associated weak type Weakened a.

Instances

Instances details
Weaken Int16 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Int16 
Instance details

Defined in Strongweak.Weaken

Weaken Int32 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Int32 
Instance details

Defined in Strongweak.Weaken

Weaken Int64 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Int64 
Instance details

Defined in Strongweak.Weaken

Weaken Int8 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Int8 
Instance details

Defined in Strongweak.Weaken

Weaken Word16 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Word16 
Instance details

Defined in Strongweak.Weaken

Weaken Word32 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Word32 
Instance details

Defined in Strongweak.Weaken

Weaken Word64 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Word64 
Instance details

Defined in Strongweak.Weaken

Weaken Word8 Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened Word8 
Instance details

Defined in Strongweak.Weaken

Weaken (Identity a) Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (Identity a) 
Instance details

Defined in Strongweak.Weaken

Weaken (NonEmpty a) Source #

Weaken non-empty lists into plain lists.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (NonEmpty a) 
Instance details

Defined in Strongweak.Weaken

type Weakened (NonEmpty a) = [a]
(Generic (f 'Strong), Generic (f 'Weak), GWeaken (Rep (f 'Strong)) (Rep (f 'Weak))) => Weaken (GenericallySW0 f) Source # 
Instance details

Defined in Strongweak.Generic

Associated Types

type Weakened (GenericallySW0 f) 
Instance details

Defined in Strongweak.Generic

Weaken (SWCoercibly a) Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (SWCoercibly a) 
Instance details

Defined in Strongweak.Weaken

type Weakened (SWCoercibly a) = a
Weaken a => Weaken [a] Source #

Decomposer. Weaken every element in a list.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened [a] 
Instance details

Defined in Strongweak.Weaken

type Weakened [a] = [Weakened a]

Methods

weaken :: [a] -> Weakened [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 Weakened (Either a b) 
Instance details

Defined in Strongweak.Weaken

type Weakened (Either a b) = Either (Weakened a) (Weakened b)

Methods

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

WeakenN n a => Weaken (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

Associated Types

type Weakened (SWChain n a) 
Instance details

Defined in Strongweak.Chain

type Weakened (SWChain n a) = WeakenedN n a

Methods

weaken :: SWChain n a -> Weakened (SWChain n a) Source #

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

Defined in Strongweak.Generic

Associated Types

type Weakened (GenericallySW s w) 
Instance details

Defined in Strongweak.Generic

type Weakened (GenericallySW s w) = w
(Weaken a, Weaken b) => Weaken (a, b) Source #

Decomposer. Weaken both elements of a tuple.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (a, b) 
Instance details

Defined in Strongweak.Weaken

type Weakened (a, b) = (Weakened a, Weakened b)

Methods

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

Weaken (Const a b) Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (Const a b) 
Instance details

Defined in Strongweak.Weaken

Methods

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

Weaken (Refined p a) Source #

Strip refined type refinement.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (Refined p a) 
Instance details

Defined in Strongweak.Weaken

type Weakened (Refined p a) = a

Methods

weaken :: Refined p a -> Weakened (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 Weakened (Vector v n a) 
Instance details

Defined in Strongweak.Weaken

type Weakened (Vector v n a) = [a]

Methods

weaken :: Vector v n a -> Weakened (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 Weakened (Refined1 p f a) 
Instance details

Defined in Strongweak.Weaken

type Weakened (Refined1 p f a) = f a

Methods

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

weakenN :: WeakenN n a => a -> WeakenedN n a Source #

class Weaken a => Strengthen a where Source #

Attempt to strengthen some Weakened 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 :: Weakened a -> Either StrengthenFailure' a Source #

Attempt to strengthen some Weakened 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 # 
Instance details

Defined in Strongweak.Strengthen

Strengthen (NonEmpty a) Source #

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

Instance details

Defined in Strongweak.Strengthen

(Generic (f 'Strong), Generic (f 'Weak), GStrengthenD (Rep (f 'Weak)) (Rep (f 'Strong)), Weaken (GenericallySW0 f)) => Strengthen (GenericallySW0 f) Source # 
Instance details

Defined in Strongweak.Generic

Strengthen (SWCoercibly a) Source # 
Instance details

Defined in Strongweak.Strengthen

Strengthen a => Strengthen [a] Source #

Decomposer. Strengthen every element in a list.

Instance details

Defined in Strongweak.Strengthen

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

Decomposer. Strengthen either side of an Either.

Instance details

Defined in Strongweak.Strengthen

StrengthenN n a => Strengthen (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

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

Defined in Strongweak.Generic

(Strengthen l, Strengthen r) => Strengthen (l, r) Source #

Decomposer. Strengthen both elements of a tuple.

Instance details

Defined in Strongweak.Strengthen

Strengthen (Const a b) Source # 
Instance details

Defined in Strongweak.Strengthen

Refine p a => Strengthen (Refined p a) Source #

Strengthen a type by refining it with a predicate.

Instance details

Defined in Strongweak.Strengthen

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

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

Instance details

Defined in Strongweak.Strengthen

Refine1 p f => Strengthen (Refined1 p f a) Source #

Strengthen a type by refining it with a functor predicate.

Instance details

Defined in Strongweak.Strengthen

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) = a
Weakened (SWChain 1 a) = Weakened a
Weakened (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 via SWChain 2 (Identity Word8) instance     Weaken (A Strong)
deriving via SWChain 2 (Identity Word8) instance Strengthen (A Strong)

Constructors

SWChain 

Fields

Instances

Instances details
Show a => Show (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

Methods

showsPrec :: Int -> SWChain n a -> ShowS #

show :: SWChain n a -> String #

showList :: [SWChain n a] -> ShowS #

Eq a => Eq (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

Methods

(==) :: SWChain n a -> SWChain n a -> Bool #

(/=) :: SWChain n a -> SWChain n a -> Bool #

Ord a => Ord (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

Methods

compare :: SWChain n a -> SWChain n a -> Ordering #

(<) :: SWChain n a -> SWChain n a -> Bool #

(<=) :: SWChain n a -> SWChain n a -> Bool #

(>) :: SWChain n a -> SWChain n a -> Bool #

(>=) :: SWChain n a -> SWChain n a -> Bool #

max :: SWChain n a -> SWChain n a -> SWChain n a #

min :: SWChain n a -> SWChain n a -> SWChain n a #

StrengthenN n a => Strengthen (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

WeakenN n a => Weaken (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

Associated Types

type Weakened (SWChain n a) 
Instance details

Defined in Strongweak.Chain

type Weakened (SWChain n a) = WeakenedN n a

Methods

weaken :: SWChain n a -> Weakened (SWChain n a) Source #

type Weakened (SWChain n a) Source # 
Instance details

Defined in Strongweak.Chain

type Weakened (SWChain n a) = WeakenedN n a

newtype SWCoercibly a Source #

A "via type" newtype for defining strongweak instances for zero-invariant, coercible newtypes.

Use like so:

deriving Weaken via SWCoercibly a

Or standalone:

via SWCoercibly a instance Weaken (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

Instances details
Strengthen (SWCoercibly a) Source # 
Instance details

Defined in Strongweak.Strengthen

UnsafeStrengthen (SWCoercibly a) Source # 
Instance details

Defined in Strongweak.Strengthen.Unsafe

Weaken (SWCoercibly a) Source # 
Instance details

Defined in Strongweak.Weaken

Associated Types

type Weakened (SWCoercibly a) 
Instance details

Defined in Strongweak.Weaken

type Weakened (SWCoercibly a) = a
type Weakened (SWCoercibly a) Source # 
Instance details

Defined in Strongweak.Weaken

type Weakened (SWCoercibly a) = a

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

data Strength Source #

Strength enumeration: it's either strong, or weak.

Primarily interesting at the type level (using DataKinds).

Constructors

Strong 
Weak 

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 }

Equations

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