Safe Haskell | None |
---|---|
Language | Haskell2010 |
LawfulConversions
Description
Conversions
The main part of the API is two functions: to
and from
. Both
perform a conversion between two types. The main difference between them
is in what the first type application parameter specifies. E.g.:
toString = to @String
fromText = from @Text
The types should be self-evident:
> :t to @String to @String :: IsSome String b => b -> String
> :t from @Text from @Text :: IsMany 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 or the reader.
Examples
combineEncodings ::ShortByteString
->ByteArray
-> [Word8
] ->ByteString
combineEncodings a b c =from
@Builder
$to
a <>to
b <>to
c
renderNameAndHeight ::Text
->Int
->Text
renderNameAndHeight name height =from
@StrictTextBuilder
$ "Height of " <>from
name <> " is " <>from
(show height)
Partial conversions
This library also captures the pattern of smart constructors via the IsSome
class, which associates a total to
conversion with its partial inverse maybeFrom
.
This captures the codec relationship between types. E.g.,
- Every
Int16
can be losslessly converted intoInt32
, but not everyInt32
can be losslessly converted intoInt16
. - Every
Text
can be converted intoByteString
via UTF-8 encoding, but not everyByteString
forms a valid UTF-8 sequence. - Every URL can be uniquely represented as
Text
, but mostText
s are not URLs unfortunately. - UTCTime, JSON, Email, etc.
Examples
Here's an example of implementing the Smart Constructor pattern.
module Percent (Percent) where import LawfulConversions newtype Percent = Percent Double instance IsSome Double Percent where to (Percent double) = double maybeFrom double = if double < 0 || double > 1 then Nothing else Just (Percent double)
You can also expand upon that and provide a default handling of invalid values effectively providing a lossy canonicalizing conversion (Surjection):
instance IsMany Double Percent where from double = if double < 0 then Percent 0 else if double > 1 then Percent 1 else Percent double
However declaring an instance of Is
would be incorrect, because this conversion is partial.
Namely, while every Percent
value can be losslessly transformed into Double
, not every Double
can be losslessly transformed into Percent
.
Synopsis
- class IsSome a b where
- class IsSome a b => IsMany a b where
- from :: a -> b
- class (IsMany a b, Is b a) => Is a b
- isSomePrism :: (IsSome a b, Choice p, Applicative f) => p b (f b) -> p a (f a)
- isManyIso :: (IsMany a b, Profunctor p, Functor f) => p b (f b) -> p a (f a)
- isIso :: (Is a b, Profunctor p, Functor f) => p b (f b) -> p a (f a)
- newtype ViaIsSome a b = ViaIsSome b
- isSomeProperties :: (IsSome a b, Eq a, Eq b, Show a, Show b, Arbitrary b) => Proxy a -> Proxy b -> [(String, Property)]
- isManyProperties :: (IsMany a b, Eq a, Eq b, Show a, Show b, Arbitrary b) => Proxy a -> Proxy b -> [(String, Property)]
- isProperties :: (Is a b, Eq a, Eq b, Show a, Show b, Arbitrary a, Arbitrary b) => Proxy a -> Proxy b -> [(String, Property)]
Typeclasses
class IsSome a b where Source #
Evidence that all values of type b
form a subset of all values of type a
.
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 b
that are not equal converting with to
produces values that are not equal as well:
\(b1, b2) -> b1 == b2 || to @a b1 /= to @a b2
maybeFrom
is a partial inverse of to
For all values of b
converting to a
and then attempting to convert back to b
always succeeds and produces a value that is equal to the original:
\b -> maybeFrom (to @a b) == Just b
Testing
For testing whether your instances conform to these laws use isSomeProperties
.
Minimal complete definition
Methods
Convert a value of a subset type to a superset type.
maybeFrom :: a -> Maybe b Source #
Partial inverse of to
.
Instances
class IsSome a b => IsMany a b where Source #
Lossy or canonicalizing conversion. Captures mappings from multiple alternative inputs into one output.
E.g.,
ByteString
can be decoded intoText
with UTF-8 leniently, replacing the invalid chars with a default char.String
has a wider range of supported chars thanText
, so some chars get replaced too.
Laws
from
is an inverse of to
\b -> b == from (to @a b)
Testing
For testing whether your instances conform to these laws use isManyProperties
.
Minimal complete definition
Nothing
Methods
Possibly lossy inverse of to
.
Surjection from a
to b
.
Particularly useful in combination with the TypeApplications
extension,
where it allows to specify the input type, e.g.:
fromText :: IsMany Text b => Text -> b fromText = from @Text
The first type application of the to
function on the other hand specifies
the output data type.
Instances
class (IsMany 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
from
is an inverse of to
For all values of b converting from b to a and then converting from a to b produces the original value:
\b -> b == from (to @a b)
to
is an inverse of from
For all values of a converting from a to b and then converting from b to a produces the original value:
\a -> a == to (from @a @b a)
Testing
For testing whether your instances conform to these laws use isProperties
.
Instance Definition
For each pair of isomorphic types (A and B) the compiler will require you to define six instances, namely: Is A B
and Is B A
, IsMany A B
and IsMany B A
, IsSome A B
and IsSome B A
.
Instances of Is
do not define any functions and serve merely as a statement that the laws are satisfied.
Example: Lazy Text and Text
instance IsSome Data.Text.Lazy.LazyText Data.Text.Text where to = LazyText.fromStrict
instance IsSome Data.Text.Text Data.Text.Lazy.LazyText where to = LazyText.toStrict
instance IsMany Data.Text.Lazy.LazyText Data.Text.Text instance IsMany Data.Text.Text Data.Text.Lazy.LazyText instance Is Data.Text.Lazy.LazyText Data.Text.Text instance Is Data.Text.Text Data.Text.Lazy.LazyText
Instances
Optics
isSomePrism :: (IsSome a b, Choice p, Applicative f) => p b (f b) -> p a (f a) Source #
Van-Laarhoven-style Prism, compatible with libraries like "lens" and "optics".
isManyIso :: (IsMany a b, Profunctor p, Functor f) => p b (f b) -> p a (f a) Source #
Van-Laarhoven-style Isomorphism, compatible with libraries like "lens" and "optics".
isIso :: (Is a b, Profunctor p, Functor f) => p b (f b) -> p a (f a) Source #
Van-Laarhoven-style Isomorphism, compatible with libraries like "lens" and "optics".
Instance derivation
Proxy data-types useful for deriving various standard instances using the DerivingVia
extension.
newtype ViaIsSome a b Source #
Helper for deriving common instances on types which have an instance of
using the IsSome
aDerivingVia
extension.
E.g.,
newtype Percent = Percent Double deriving newtype (Show, Eq, Ord) deriving (Read, 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 b |
Instances
Testing
isSomeProperties :: (IsSome a b, Eq a, Eq b, Show a, Show b, Arbitrary 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) (isSomeProperties @Int32 @Int16 Proxy Proxy)
isManyProperties :: (IsMany a b, Eq a, Eq b, Show a, Show b, Arbitrary b) => Proxy a -> Proxy b -> [(String, Property)] Source #
Properties testing whether an instance satisfies the laws of IsMany
.
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 "IsMany laws" do traverse_ (uncurry prop) (isManyProperties @String @Text Proxy Proxy)
isProperties :: (Is a b, Eq a, Eq b, Show a, Show b, Arbitrary a, Arbitrary 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) (isProperties @Int32 @Word32 Proxy Proxy)