strongweak-0.3.1: Convert between strong and weak representations of types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Strongweak.Weaken

Synopsis

Weaken class

class Weaken a where Source #

Transform an a to a Weaken a.

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

Law: a === b -> weaken a === weaken b

Instances should either handle an invariant, or decompose. See Strongweak for a discussion on this design.

Associated Types

type Weak a :: Type Source #

The type to weaken to.

Methods

weaken :: a -> Weak a Source #

Transform a strong value to its associated weak one.

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 a => Weaken (Identity a) Source #

Decomposer.

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 (Maybe a) Source #

Decomposer.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Maybe a) Source #

Methods

weaken :: Maybe a -> Weak (Maybe 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.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Either a b) Source #

Methods

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

Weaken (Vector n a) Source #

Weaken sized vectors into plain lists.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Vector n a) Source #

Methods

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

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

Decomposer.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (a, b) Source #

Methods

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

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

Decomposer.

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 the refinement from refined types.

Instance details

Defined in Strongweak.Weaken

Associated Types

type Weak (Refined p a) Source #

Methods

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

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

Lift a function on a weak type to the associated strong type.

SW helper

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