isomorphism-class-0.2.0.3: Lawful typeclasses for conversion between types
Safe HaskellNone
LanguageHaskell2010

IsomorphismClass

Description

Lawful solution to the conversion problem.

Conversion problem

Have you ever looked for a toString function? How often do you import Data.Text.Lazy only to call its fromStrict? How about importing Data.ByteString.Builder only to call its toLazyByteString and then importing Data.ByteString.Lazy only to call its toStrict?

Those all are instances of one pattern. They are conversions between representations of the same information. Codebases that don't attempt to abstract over this pattern tend to be sprawling with this type of boilerplate. It's noise to the codereader, it's a burden to the implementor and the maintainer.

Why another conversion library?

Many libraries exist that approach the conversion problem. However most of them provide lawless typeclasses leaving it up to the author of the instance to define what makes a proper conversion. This results in inconsistencies across instances, their behaviour not being evident to the user and no way to check whether an instance is correct.

This library tackles this problem with a lawful typeclass, making it evident what any of its instances do and it provides property-tests for you to validate your instances.

The insight

The key insight of this library is that if you add a requirement for the conversion to be lossless and to have a mirror conversion in the opposite direction, there usually appears to be only one way of defining it. That makes it very clear what the conversion does to the user and how to define it to the author of the conversion. It also gives a clear criteria for validating whether the instances are correct, which can be encoded in property-tests.

That insight itself stems from an observation that almost all of the practical conversions in Haskell share a property: you can restore the original data from its converted form. E.g., you can get a text from a text-builder and you can create a text-builder from a text, you can convert a bytestring into a list of bytes and vice-versa, bytestring to/from bytearray, strict bytestring to/from lazy, list to/from sequence, sequence to/from vector, set of ints to/from int-set. In other words, it's always a two-way street with them and there's a lot of instances of this pattern.

UX

A few other accidental findings like encoding this property with recursive typeclass constraints and fine-tuning for the use of the TypeApplications extension resulted in a terse and clear API.

Essentially the whole API is just two functions: to and from. Both perform a conversion between two types. The only difference between them is in what the first type application parameter specifies. E.g.:

toString = to @String
fromText = from @Text

The types are self-evident:

> :t to @String
to @String :: Is String b => b -> String
> :t from @Text
from @Text :: Is Text b => Text -> b

In other words to and from let you explicitly specify either the source or the target type of a conversion when you need to help the type inferencer.

Here are more practical examples:

renderNameAndHeight :: Text -> Int -> Text
renderNameAndHeight name height =
  from @StrictTextBuilder $
    "Height of " <> to name <> " is " <> to (show height)
combineEncodings :: ShortByteString -> ByteArray -> ByteString -> [Word8]
combineEncodings a b c =
  from @Builder $
    to a <> to b <> to c

Partial conversions

Atop of all said this library also captures the notion of smart constructors via the IsSome class, which associates a total to conversion with partial maybeFrom.

This captures the codec relationship between types. E.g.,

  • Every Int16 can be losslessly converted into Int32, but not every Int32 can be losslessly converted into Int16.
  • Every Text can be converted into ByteString via UTF-8 encoding, but not every ByteString forms a valid UTF-8 sequence.
  • Every URL can be uniquely represented as Text, but most Texts are not URLs unfortunately.
Synopsis

Typeclasses

class (IsSome a b, Is b a) => Is a b Source #

Bidirectional conversion between two types with no loss of information.

The bidirectionality is encoded via a recursive dependency with arguments flipped.

You can read the signature Is a b as "B is A".

Laws

B is isomorphic to A if and only if there exists a conversion from B to A (to) and a conversion from A to B (from) such that:

  • from . to = id - For all values of B converting from B to A and then converting from A to B produces a value that is identical to the original.
  • to . from = id - For all values of A converting from A to B and then converting from B to A produces a value that is identical to the original.

For testing whether your instances conform to these laws use isLawsProperties.

Instance Definition

For each pair of isomorphic types (A and B) the compiler will require you to define four instances, namely: Is A B and Is B A as well as IsSome A B and IsSome B A.

Instances

Instances details
Is ByteArray Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteStringBuilder

Is ByteArray ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndByteString

Is ByteArray ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteString

Is ByteArray ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndShortByteString

Is Builder ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteStringBuilder

Is Builder ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteStringBuilder

Is Builder ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndLazyByteStringBuilder

Is Builder ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndShortByteString

Is ByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndByteString

Is ByteString Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteStringBuilder

Is ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteString

Is ByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndShortByteString

Is ByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteString

Is ByteString Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndLazyByteStringBuilder

Is ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteString

Is ByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndShortByteString

Is ShortByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndShortByteString

Is ShortByteString Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndShortByteString

Is ShortByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndShortByteString

Is ShortByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndShortByteString

Is Int16 Word16 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int16AndWord16

Is Int32 Word32 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int32AndWord32

Is Int64 Word64 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int64AndWord64

Is Int8 Word8 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int8AndWord8

Is Word16 Int16 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int16AndWord16

Is Word32 Int32 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int32AndWord32

Is Word64 Int64 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int64AndWord64

Is Word8 Int8 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int8AndWord8

Is Text Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndText

Is Text Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndText

Is Text StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.StrictTextBuilderAndText

Is Builder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndText

Is Builder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndLazyTextBuilder

Is Builder StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndStrictTextBuilder

Is Text Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndText

Is Text Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndLazyTextBuilder

Is Text StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndStrictTextBuilder

Is StrictBuilder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.StrictTextBuilderAndText

Is StrictBuilder Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndStrictTextBuilder

Is StrictBuilder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndStrictTextBuilder

Is Int Word Source # 
Instance details

Defined in IsomorphismClass.Relations.IntAndWord

Is Word Int Source # 
Instance details

Defined in IsomorphismClass.Relations.IntAndWord

Is a a Source #

Any type is isomorphic to itself.

Instance details

Defined in IsomorphismClass.Classes.Is

Is ByteArray [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndWord8List

Is Builder [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndWord8List

Is ByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndWord8List

Is ByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndWord8List

Is ShortByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.ShortByteStringAndWord8List

Is IntSet (Set Int) Source # 
Instance details

Defined in IsomorphismClass.Relations.IntSetAndSetOfInts

Is (Set Int) IntSet Source # 
Instance details

Defined in IsomorphismClass.Relations.IntSetAndSetOfInts

Is [Word8] ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndWord8List

Is [Word8] Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndWord8List

Is [Word8] ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndWord8List

Is [Word8] ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndWord8List

Is [Word8] ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ShortByteStringAndWord8List

Is (Seq a) (Vector a) Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndSeq

Is (Seq a) [a] Source # 
Instance details

Defined in IsomorphismClass.Relations.ListAndSeq

Is (Vector a) (Seq a) Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndSeq

Is (Vector a) [a] Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndList

Is [a] (Seq a) Source # 
Instance details

Defined in IsomorphismClass.Relations.ListAndSeq

Is [a] (Vector a) Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndList

Is (IntMap v) (Map Int v) Source # 
Instance details

Defined in IsomorphismClass.Relations.IntMapAndMapOfInt

Is (Map Int v) (IntMap v) Source # 
Instance details

Defined in IsomorphismClass.Relations.IntMapAndMapOfInt

class IsSome sup sub where Source #

Evidence that all values of type sub form a subset of all values of type sup.

From Wikipedia:

In mathematics, a set A is a subset of a set B if all elements of A are also elements of B; B is then a superset of A. It is possible for A and B to be equal; if they are unequal, then A is a proper subset of B. The relationship of one set being a subset of another is called inclusion (or sometimes containment). A is a subset of B may also be expressed as B includes (or contains) A or A is included (or contained) in B. A k-subset is a subset with k elements.

Laws

to is injective

For every two values of type sub that are not equal converting with to will always produce values that are not equal.

\(a, b) -> a == b || to a /= to b

maybeFrom is an inverse of to

For all values of sub converting to sup and then attempting to convert back to sub always succeeds and produces a value that is equal to the original.

\a -> maybeFrom (to a) == Just a

For testing whether your instances conform to these laws use isSomeLawsProperties.

Minimal complete definition

to

Methods

to :: sub -> sup Source #

Convert a value of a subset type to a superset type.

This function is injective non-surjective.

maybeFrom :: sup -> Maybe sub Source #

Partial inverse of to.

This function is a partial bijection.

default maybeFrom :: IsSome sub sup => sup -> Maybe sub Source #

Instances

Instances details
IsSome ByteArray Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteStringBuilder

IsSome ByteArray ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndByteString

IsSome ByteArray ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteString

IsSome ByteArray ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndShortByteString

IsSome Builder ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteStringBuilder

IsSome Builder ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteStringBuilder

IsSome Builder ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndLazyByteStringBuilder

IsSome Builder ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndShortByteString

IsSome ByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndByteString

IsSome ByteString Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteStringBuilder

IsSome ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteString

IsSome ByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndShortByteString

IsSome ByteString Text Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndText

IsSome ByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndLazyByteString

IsSome ByteString Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndLazyByteStringBuilder

IsSome ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndLazyByteString

IsSome ByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndShortByteString

IsSome ByteString Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndLazyText

IsSome ShortByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndShortByteString

IsSome ShortByteString Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndShortByteString

IsSome ShortByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndShortByteString

IsSome ShortByteString ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndShortByteString

IsSome Int16 Word16 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int16AndWord16

IsSome Int32 Word32 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int32AndWord32

IsSome Int64 Word64 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int64AndWord64

IsSome Int8 Word8 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int8AndWord8

IsSome Word16 Int16 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int16AndWord16

IsSome Word32 Int32 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int32AndWord32

IsSome Word64 Int64 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int64AndWord64

IsSome Word8 Int8 Source # 
Instance details

Defined in IsomorphismClass.Relations.Int8AndWord8

IsSome Text Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndText

IsSome Text Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndText

IsSome Text StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.StrictTextBuilderAndText

IsSome Builder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndText

IsSome Builder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndLazyTextBuilder

IsSome Builder StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndStrictTextBuilder

IsSome Text Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndText

IsSome Text Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndLazyTextBuilder

IsSome Text StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndStrictTextBuilder

IsSome StrictBuilder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.StrictTextBuilderAndText

IsSome StrictBuilder Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndStrictTextBuilder

IsSome StrictBuilder Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndStrictTextBuilder

IsSome String Text Source # 
Instance details

Defined in IsomorphismClass.Relations.StringAndText

IsSome String Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextBuilderAndString

IsSome String Text Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyTextAndString

IsSome String StrictBuilder Source # 
Instance details

Defined in IsomorphismClass.Relations.StrictTextBuilderAndString

IsSome Int Word Source # 
Instance details

Defined in IsomorphismClass.Relations.IntAndWord

IsSome Word Int Source # 
Instance details

Defined in IsomorphismClass.Relations.IntAndWord

IsSome a a Source #

Every type is isomorphic to itself.

Instance details

Defined in IsomorphismClass.Classes.IsSome

Methods

to :: a -> a Source #

maybeFrom :: a -> Maybe a Source #

IsSome sup Void Source #

The empty set has no elements, and therefore is vacuously a subset of any set.

Instance details

Defined in IsomorphismClass.Classes.IsSome

Methods

to :: Void -> sup Source #

maybeFrom :: sup -> Maybe Void Source #

IsSome ByteArray [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndWord8List

IsSome Builder [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndWord8List

IsSome ByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndWord8List

IsSome ByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndWord8List

IsSome ShortByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass.Relations.ShortByteStringAndWord8List

IsSome IntSet (Set Int) Source # 
Instance details

Defined in IsomorphismClass.Relations.IntSetAndSetOfInts

IsSome sup sub => IsSome sup (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

to :: ViaIsSome sup sub -> sup Source #

maybeFrom :: sup -> Maybe (ViaIsSome sup sub) Source #

IsSome (Set Int) IntSet Source # 
Instance details

Defined in IsomorphismClass.Relations.IntSetAndSetOfInts

IsSome [Word8] ByteArray Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteArrayAndWord8List

IsSome [Word8] Builder Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringBuilderAndWord8List

IsSome [Word8] ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ByteStringAndWord8List

IsSome [Word8] ByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.LazyByteStringAndWord8List

IsSome [Word8] ShortByteString Source # 
Instance details

Defined in IsomorphismClass.Relations.ShortByteStringAndWord8List

IsSome (Seq a) (Vector a) Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndSeq

Methods

to :: Vector a -> Seq a Source #

maybeFrom :: Seq a -> Maybe (Vector a) Source #

IsSome (Seq a) [a] Source # 
Instance details

Defined in IsomorphismClass.Relations.ListAndSeq

Methods

to :: [a] -> Seq a Source #

maybeFrom :: Seq a -> Maybe [a] Source #

IsSome (Vector a) (Seq a) Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndSeq

Methods

to :: Seq a -> Vector a Source #

maybeFrom :: Vector a -> Maybe (Seq a) Source #

IsSome (Vector a) [a] Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndList

Methods

to :: [a] -> Vector a Source #

maybeFrom :: Vector a -> Maybe [a] Source #

IsSome [a] (Seq a) Source # 
Instance details

Defined in IsomorphismClass.Relations.ListAndSeq

Methods

to :: Seq a -> [a] Source #

maybeFrom :: [a] -> Maybe (Seq a) Source #

IsSome [a] (Vector a) Source # 
Instance details

Defined in IsomorphismClass.Relations.BoxedVectorAndList

Methods

to :: Vector a -> [a] Source #

maybeFrom :: [a] -> Maybe (Vector a) Source #

IsSome (IntMap v) (Map Int v) Source # 
Instance details

Defined in IsomorphismClass.Relations.IntMapAndMapOfInt

Methods

to :: Map Int v -> IntMap v Source #

maybeFrom :: IntMap v -> Maybe (Map Int v) Source #

IsSome (Map Int v) (IntMap v) Source # 
Instance details

Defined in IsomorphismClass.Relations.IntMapAndMapOfInt

Methods

to :: IntMap v -> Map Int v Source #

maybeFrom :: Map Int v -> Maybe (IntMap v) Source #

from :: Is a b => a -> b Source #

to in reverse direction.

Particularly useful in combination with the TypeApplications extension, where it allows to specify the input type, e.g.:

fromText :: Is Text b => Text -> b
fromText = from @Text

The first type application of the to function on the other hand specifies the output data type.

Optics

isSomePrism :: (IsSome a b, Choice p, Applicative f) => p b (f b) -> p a (f a) Source #

Van-Laarhoven-style Prism, compatible with the "lens" library.

isIso :: (Is a b, Profunctor p, Functor f) => p b (f b) -> p a (f a) Source #

Van-Laarhoven-style Isomorphism, compatible with the "lens" library.

Instance derivation

Proxy data-types useful for deriving various standard instances using the DerivingVia extension.

newtype ViaIsSome sup sub Source #

Helper for deriving common instances on types which have an instance of IsSome sup using the DerivingVia extension.

E.g.,

newtype Percent = Percent Double
  deriving newtype (Show, Eq, Ord)
  deriving (Read, IsString, Arbitrary) via (ViaIsSome Double Percent)

instance IsSome Double Percent where
  to (Percent double) = double
  maybeFrom double =
    if double < 0 || double > 1
      then Nothing
      else Just (Percent double)

In the code above all the instances that are able to construct the values of Percent are automatically derived based on the IsSome Double Percent instance. This guarantees that they only construct values that pass thru the checks defined in maybeFrom.

Constructors

ViaIsSome sub 

Instances

Instances details
IsSome sup sub => IsSome sup (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

to :: ViaIsSome sup sub -> sup Source #

maybeFrom :: sup -> Maybe (ViaIsSome sup sub) Source #

(IsSome sup sub, Arbitrary sup) => Arbitrary (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

arbitrary :: Gen (ViaIsSome sup sub) #

shrink :: ViaIsSome sup sub -> [ViaIsSome sup sub] #

(IsSome sup sub, IsString sup) => IsString (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

fromString :: String -> ViaIsSome sup sub #

(IsSome sup sub, Read sup) => Read (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

readsPrec :: Int -> ReadS (ViaIsSome sup sub) #

readList :: ReadS [ViaIsSome sup sub] #

readPrec :: ReadPrec (ViaIsSome sup sub) #

readListPrec :: ReadPrec [ViaIsSome sup sub] #

(IsSome sup sub, Show sup) => Show (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

showsPrec :: Int -> ViaIsSome sup sub -> ShowS #

show :: ViaIsSome sup sub -> String #

showList :: [ViaIsSome sup sub] -> ShowS #

(IsSome sup sub, Eq sup) => Eq (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

(==) :: ViaIsSome sup sub -> ViaIsSome sup sub -> Bool #

(/=) :: ViaIsSome sup sub -> ViaIsSome sup sub -> Bool #

(IsSome sup sub, Ord sup) => Ord (ViaIsSome sup sub) Source # 
Instance details

Defined in IsomorphismClass.Proxies.ViaIsSome

Methods

compare :: ViaIsSome sup sub -> ViaIsSome sup sub -> Ordering #

(<) :: ViaIsSome sup sub -> ViaIsSome sup sub -> Bool #

(<=) :: ViaIsSome sup sub -> ViaIsSome sup sub -> Bool #

(>) :: ViaIsSome sup sub -> ViaIsSome sup sub -> Bool #

(>=) :: ViaIsSome sup sub -> ViaIsSome sup sub -> Bool #

max :: ViaIsSome sup sub -> ViaIsSome sup sub -> ViaIsSome sup sub #

min :: ViaIsSome sup sub -> ViaIsSome sup sub -> ViaIsSome sup sub #

Testing

isSomeLawsProperties :: (IsSome a b, Eq a, Eq b, Show a, Arbitrary b, Show b) => Proxy a -> Proxy b -> [(String, Property)] Source #

Properties testing whether an instance satisfies the laws of IsSome.

The instance is identified via the proxy types that you provide.

E.g., here's how you can integrate it into an Hspec test-suite:

spec = do
  describe "IsSome laws" do
    traverse_
      (uncurry prop)
      (isSomeLawsProperties @Int32 @Int16 Proxy Proxy)

isLawsProperties :: (Is a b, Eq a, Eq b, Arbitrary a, Show a, Arbitrary b, Show b) => Proxy a -> Proxy b -> [(String, Property)] Source #

Properties testing whether an instance satisfies the laws of Is.

The instance is identified via the proxy types that you provide.

E.g., here's how you can integrate it into an Hspec test-suite:

spec = do
  describe "Is laws" do
    traverse_
      (uncurry prop)
      (isLawsProperties @Int32 @Word32 Proxy Proxy)