isomorphism-class-0.1.0.1: Isomorphism typeclass solving the conversion problem
Safe HaskellNone
LanguageHaskell2010

IsomorphismClass

Description

Isomorphism law as a 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.Text only to to call its unpack? How about going thru the always fun sequence of importing Data.ByteString.Builder only to 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 all 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 and their behaviour being not evident to the user.

This library tackles this problem with a lawful typeclass, making it evident what any of its instances do.

The law

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.

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 bytestring from a builder and you can create a builder from a bytestring, you can convert a text into a list of chars 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 very terse yet 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.:

fromString = from @String
toText = to @Text

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 @Builder $
    "Height of " <> to name <> " is " <> showAs height
combineEncodings :: ShortByteString -> ByteArray -> ByteString -> [Word8]
combineEncodings a b c =
  from @Builder $
    to a <> to b <> to c
Synopsis

Typeclass

class IsomorphicTo b a => IsomorphicTo a b where 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 IsomorphicTo a b as "B is isomorphic to A".

Laws

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

  • from . to = 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.
  • to . from = 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.

Usage

This class is particularly easy to use in combination with the TypeApplications extension making it clear to the reader what sort of conversion he sees. E.g.,

fromString = from @String
toText = to @Text

The types are also self-evident:

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

Instance Definition

For each pair of isomorphic types (A and B) the compiler will require you to define two instances, namely: IsomorphicTo A B and IsomorphicTo B A.

Methods

to :: b -> a Source #

Instances

Instances details
IsomorphicTo Bool Bool Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Bool -> Bool Source #

IsomorphicTo Char Char Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Char -> Char Source #

IsomorphicTo Double Double Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Double -> Double Source #

IsomorphicTo Float Float Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Float -> Float Source #

IsomorphicTo Int Int Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int -> Int Source #

IsomorphicTo Int Word Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word -> Int Source #

IsomorphicTo Int8 Int8 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int8 -> Int8 Source #

IsomorphicTo Int8 Word8 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word8 -> Int8 Source #

IsomorphicTo Int16 Int16 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int16 -> Int16 Source #

IsomorphicTo Int16 Word16 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word16 -> Int16 Source #

IsomorphicTo Int32 Int32 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int32 -> Int32 Source #

IsomorphicTo Int32 Word32 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word32 -> Int32 Source #

IsomorphicTo Int64 Int64 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int64 -> Int64 Source #

IsomorphicTo Int64 Word64 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word64 -> Int64 Source #

IsomorphicTo Integer Integer Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Integer -> Integer Source #

IsomorphicTo Rational Rational Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Rational -> Rational Source #

IsomorphicTo Word Int Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int -> Word Source #

IsomorphicTo Word Word Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word -> Word Source #

IsomorphicTo Word8 Int8 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int8 -> Word8 Source #

IsomorphicTo Word8 Word8 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word8 -> Word8 Source #

IsomorphicTo Word16 Int16 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int16 -> Word16 Source #

IsomorphicTo Word16 Word16 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word16 -> Word16 Source #

IsomorphicTo Word32 Int32 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int32 -> Word32 Source #

IsomorphicTo Word32 Word32 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word32 -> Word32 Source #

IsomorphicTo Word64 Int64 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Int64 -> Word64 Source #

IsomorphicTo Word64 Word64 Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Word64 -> Word64 Source #

IsomorphicTo String Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> String Source #

IsomorphicTo String Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> String Source #

IsomorphicTo String Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> String Source #

IsomorphicTo ShortByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ShortByteString ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ShortByteString ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ShortByteString Builder Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ShortByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ShortByteString Array Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString Builder Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString Array Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Array -> ByteString Source #

IsomorphicTo ByteString ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString Builder Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString ByteArray Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString Array Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Array -> ByteString Source #

IsomorphicTo Builder ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo Builder ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo Builder ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo Builder Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> Builder Source #

IsomorphicTo Builder ByteArray Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteArray -> Builder Source #

IsomorphicTo Builder Array Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Array -> Builder Source #

IsomorphicTo IntSet IntSet Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: IntSet -> IntSet Source #

IsomorphicTo ByteArray ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteArray ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteArray ByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteArray Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> ByteArray Source #

IsomorphicTo ByteArray ByteArray Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteArray Array Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Array -> ByteArray Source #

IsomorphicTo Builder String Source #

Performs replacement on invalid Unicode chars in the string.

Instance details

Defined in IsomorphismClass

Methods

to :: String -> Builder Source #

IsomorphicTo Builder Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> Builder Source #

IsomorphicTo Builder Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> Builder Source #

IsomorphicTo Builder Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> Builder Source #

IsomorphicTo Text String Source #

Performs replacement on invalid Unicode chars in the string.

Instance details

Defined in IsomorphismClass

Methods

to :: String -> Text Source #

IsomorphicTo Text Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> Text Source #

IsomorphicTo Text Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> Text Source #

IsomorphicTo Text Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> Text0 Source #

IsomorphicTo Text String Source #

Performs replacement on invalid Unicode chars in the string.

Instance details

Defined in IsomorphismClass

Methods

to :: String -> Text Source #

IsomorphicTo Text Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> Text Source #

IsomorphicTo Text Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text0 -> Text Source #

IsomorphicTo Text Text Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Text -> Text Source #

IsomorphicTo Array ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo Array ByteString Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteString -> Array Source #

IsomorphicTo Array ByteString Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteString -> Array Source #

IsomorphicTo Array Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> Array Source #

IsomorphicTo Array ByteArray Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteArray -> Array Source #

IsomorphicTo ShortByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo ByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: [Word8] -> ByteString Source #

IsomorphicTo ByteString [Word8] Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: [Word8] -> ByteString Source #

IsomorphicTo Builder [Word8] Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: [Word8] -> Builder Source #

IsomorphicTo IntSet (Set Int) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Set Int -> IntSet Source #

IsomorphicTo ByteArray [Word8] Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: [Word8] -> ByteArray Source #

IsomorphicTo Array [Word8] Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: [Word8] -> Array Source #

IsomorphicTo [Word8] ShortByteString Source # 
Instance details

Defined in IsomorphismClass

IsomorphicTo [Word8] ByteString Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteString -> [Word8] Source #

IsomorphicTo [Word8] ByteString Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteString -> [Word8] Source #

IsomorphicTo [Word8] Builder Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Builder -> [Word8] Source #

IsomorphicTo [Word8] ByteArray Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: ByteArray -> [Word8] Source #

IsomorphicTo [Word8] Array Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Array -> [Word8] Source #

IsomorphicTo (Set Int) IntSet Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: IntSet -> Set Int Source #

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

Defined in IsomorphismClass

Methods

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

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

Defined in IsomorphismClass

Methods

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

IsomorphicTo [a] [a] Source # 
Instance details

Defined in IsomorphismClass

Methods

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

IsomorphicTo (Maybe a) (Maybe a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Maybe a -> Maybe a Source #

IsomorphicTo (First a) (First a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: First a -> First a Source #

IsomorphicTo (Last a) (Last a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Last a -> Last a Source #

IsomorphicTo (Sum a) (Sum a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Sum a -> Sum a Source #

IsomorphicTo (Product a) (Product a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Product a -> Product a Source #

IsomorphicTo (IntMap a) (IntMap a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: IntMap a -> IntMap a Source #

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

Defined in IsomorphismClass

Methods

to :: Vector a -> Seq a Source #

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

Defined in IsomorphismClass

Methods

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

IsomorphicTo (Seq a) (Seq a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Seq a -> Seq a Source #

IsomorphicTo (Set a) (Set a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Set a -> Set a Source #

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

Defined in IsomorphismClass

Methods

to :: Seq a -> Vector a Source #

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

Defined in IsomorphismClass

Methods

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

IsomorphicTo (Vector a) (Vector a) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Vector a -> Vector a Source #

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

Defined in IsomorphismClass

Methods

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

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

Defined in IsomorphismClass

Methods

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

IsomorphicTo (Either a b) (Either a b) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Either a b -> Either a b Source #

IsomorphicTo (Map k v) (Map k v) Source # 
Instance details

Defined in IsomorphismClass

Methods

to :: Map k v -> Map k v Source #

from :: forall a b. IsomorphicTo b a => 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.:

fromString :: IsomorphicTo a String => String -> a
fromString = from @String

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

Common Utilities

showAs :: forall b a. (IsomorphicTo String b, Show a) => a -> b Source #

A utility, which uses the Show instance to produce a value that String is isomorphic to.

It lets you generalize over the functions like the following:

showAsText :: Show a => a -> Text
showAsText = showAs @Text
showAsBuilder :: Show a => a -> Builder
showAsBuilder = showAs @Builder