| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Witch
Description
The Witch package is a library that allows you to confidently convert values between various types. This module exports everything you need to perform conversions or define your own. It is designed to be imported unqualified, so getting started is as easy as:
>>>import Witch
In typical usage, you will most likely use into for
From instances and tryInto for
TryFrom instances.
Synopsis
- class From source target where
- from :: source -> target
- into :: forall target source. From source target => source -> target
- class TryFrom source target where
- tryFrom :: source -> Either (TryFromException source target) target
- tryInto :: forall target source. TryFrom source target => source -> Either (TryFromException source target) target
- as :: forall source. source -> source
- over :: forall target source. (From source target, From target source) => (target -> target) -> source -> source
- via :: forall through source target. (From source through, From through target) => source -> target
- tryVia :: forall through source target. (TryFrom source through, TryFrom through target) => source -> Either (TryFromException source target) target
- maybeTryFrom :: (source -> Maybe target) -> source -> Either (TryFromException source target) target
- eitherTryFrom :: Exception exception => (source -> Either exception target) -> source -> Either (TryFromException source target) target
- unsafeFrom :: forall source target. (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target
- unsafeInto :: forall target source. (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target
- liftedFrom :: forall source target. (TryFrom source target, Lift target, Show source, Typeable source, Typeable target) => source -> Q (TExp target)
- liftedInto :: forall target source. (TryFrom source target, Lift target, Show source, Typeable source, Typeable target) => source -> Q (TExp target)
- data TryFromException source target = TryFromException source (Maybe SomeException)
Type classes
From
class From source target where Source #
This type class is for converting values from some source type into
some other target type. The constraint means that
you can convert from a value of type From source targetsource into a value of type
target.
This type class is for conversions that cannot fail. If your conversion can
fail, consider implementing TryFrom instead.
Minimal complete definition
Nothing
Methods
from :: source -> target Source #
This method implements the conversion of a value between types. At call
sites you will usually want to use into instead of this method.
The default implementation of this method simply calls coerce,
which works for types that have the same runtime representation. This
means that for newtypes you do not need to implement this method at
all. For example:
>>>newtype Name = Name String>>>instance 'From' Name String>>>instance 'From' String Name
Instances
into :: forall target source. From source target => source -> target Source #
This is the same as from except that the type variables are in the
opposite order.
-- Avoid this: from x :: t -- Prefer this: into @t x
TryFrom
class TryFrom source target where Source #
This type class is for converting values from some source type into
some other target type. The constraint means
that you may be able to convert from a value of type TryFrom source targetsource into a value
of type target, but that conversion may fail at runtime.
This type class is for conversions that can fail. If your conversion cannot
fail, consider implementing From instead.
Methods
tryFrom :: source -> Either (TryFromException source target) target Source #
This method implements the conversion of a value between types. At call
sites you will usually want to use tryInto instead of this method.
Consider using maybeTryFrom or eitherTryFrom to implement this
method.
Instances
tryInto :: forall target source. TryFrom source target => source -> Either (TryFromException source target) target Source #
This is the same as tryFrom except that the type variables are
in the opposite order.
-- Avoid this: tryFrom x :: Either (TryFromException s t) t -- Prefer this: tryInto @t x
Utilities
as :: forall source. source -> source Source #
This is the same as id. This can be an ergonomic way to pin down a
polymorphic type in a function pipeline. For example:
-- Avoid this: f . (\ x -> x :: Int) . g -- Prefer this: f . as @Int . g
over :: forall target source. (From source target, From target source) => (target -> target) -> source -> source Source #
This function converts from some source type into some target type,
applies the given function, then converts back into the source type. This
is useful when you have two types that are isomorphic but some function
that only works with one of them.
-- Avoid this: from @t . f . into @t -- Prefer this: over @t f
via :: forall through source target. (From source through, From through target) => source -> target Source #
This function first converts from some source type into some through
type, and then converts that into some target type. Usually this is used
when writing From instances. Sometimes this can be used to work
around the lack of an instance that should probably exist.
-- Avoid this: from @u . into @u -- Prefer this: via @u
tryVia :: forall through source target. (TryFrom source through, TryFrom through target) => source -> Either (TryFromException source target) target Source #
This is similar to via except that it works with TryFrom
instances instead. This function is especially convenient because juggling
the types in the TryFromException can be tedious.
-- Avoid this:
case tryInto @u x of
Left _ -> Left ...
Right y -> case tryFrom @u y of
Left _ -> Left ...
Right z -> Right z
-- Prefer this:
tryVia @umaybeTryFrom :: (source -> Maybe target) -> source -> Either (TryFromException source target) target Source #
eitherTryFrom :: Exception exception => (source -> Either exception target) -> source -> Either (TryFromException source target) target Source #
Unsafe
These functions should only be used in two circumstances: When you know
a conversion is safe even though you can't prove it to the compiler, and
when you're alright with your program crashing if the conversion fails.
In all other cases you should prefer the normal conversion functions like
tryFrom. And if you're converting a literal value,
consider using the Template Haskell conversion functions like
liftedFrom.
unsafeFrom :: forall source target. (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target Source #
This function is like tryFrom except that it will throw an
impure exception if the conversion fails.
-- Avoid this: either throw id . tryFrom @s -- Prefer this: unsafeFrom @s
unsafeInto :: forall target source. (HasCallStack, TryFrom source target, Show source, Typeable source, Typeable target) => source -> target Source #
This function is like tryInto except that it will throw an impure
exception if the conversion fails.
-- Avoid this: either throw id . tryInto @t -- Prefer this: unsafeInto @t
Template Haskell
This library uses typed Template Haskell, which may be a little
different than what you're used to. Normally Template Haskell uses the
$(...) syntax for splicing in things to run at compile time. The typed
variant uses the $$(...) syntax for splices, doubling up on the dollar
signs. Other than that, using typed Template Haskell should be pretty
much the same as using regular Template Haskell.
liftedFrom :: forall source target. (TryFrom source target, Lift target, Show source, Typeable source, Typeable target) => source -> Q (TExp target) Source #
This is like unsafeFrom except that it works at compile time
rather than runtime.
-- Avoid this: unsafeFrom @s "some literal" -- Prefer this: $$(liftedFrom @s "some literal")
liftedInto :: forall target source. (TryFrom source target, Lift target, Show source, Typeable source, Typeable target) => source -> Q (TExp target) Source #
This is like unsafeInto except that it works at compile time
rather than runtime.
-- Avoid this: unsafeInto @t "some literal" -- Prefer this: $$(liftedInto @t "some literal")
Data types
data TryFromException source target Source #
This exception is thrown when a TryFrom conversion fails. It has the
original source value that caused the failure and it knows the target
type it was trying to convert into. It also has an optional
SomeException for communicating what went wrong while
converting.
Constructors
| TryFromException source (Maybe SomeException) |
Instances
| (Show source, Typeable source, Typeable target) => Show (TryFromException source target) Source # | |
Defined in Witch.TryFromException Methods showsPrec :: Int -> TryFromException source target -> ShowS # show :: TryFromException source target -> String # showList :: [TryFromException source target] -> ShowS # | |
| (Show source, Typeable source, Typeable target) => Exception (TryFromException source target) Source # | |
Defined in Witch.TryFromException Methods toException :: TryFromException source target -> SomeException # fromException :: SomeException -> Maybe (TryFromException source target) # displayException :: TryFromException source target -> String # | |
| From (TryFromException s u) (TryFromException s t) Source # | Uses |
Defined in Witch.Instances Methods from :: TryFromException s u -> TryFromException s t Source # | |
Notes
Motivation
Haskell provides many ways to convert between common types, and core
libraries add even more. It can be challenging to know which function to
use when converting from some source type a to some target type b. It
can be even harder to know if that conversion is safe or if there are any
pitfalls to watch out for.
This library tries to address that problem by providing a common
interface for converting between types. The From type class
is for conversions that cannot fail, and the TryFrom type
class is for conversions that can fail. These type classes are inspired
by the From
trait in Rust.
Alternatives
Many Haskell libraries already provide similar functionality. How is this library different?
Coercible: This type class is solved by the compiler, but it only works for types that have the same runtime representation. This is very convenient fornewtypes, but it does not work for converting between arbitrary types likeInt8andInt16.Convertible: This popular conversion type class is similar to what this library provides. The main difference is that it does not differentiate between conversions that can fail and those that cannot.From: This type class is almost identical to what this library provides. Unfortunately it is part of thebasementpackage, which is an alternative standard library that some people may not want to depend on.Inj: This type class requires instances to be an injection, which means that no two input values should map to the same output. That restriction prohibits many useful instances. Also many instances throw impure exceptions.
In addition to those general-purpose type classes, there are many alternatives for more specific conversions. How does this library compare to those?
- Monomorphic conversion functions like
Data.Text.packare explicit but not necessarily convenient. It can be tedious to manage the imports necessary to use the functions. And if you want to put them in a custom prelude, you will have to come up with your own names. - Polymorphic conversion methods like
toEnumare more convenient but may have unwanted semantics or runtime behavior. For example theEnumtype class is more or less tied to theIntdata type and frequently throws impure exceptions. - Polymorphic conversion functions like
fromIntegralare very convenient. Unfortunately it can be challenging to know which types have the instances necessary to make the conversion possible. And even if the conversion is possible, is it safe? For example converting a negativeIntinto aWordwill overflow, which may be surprising.
Instances
When should you add a From (or TryFrom)
instance for some pair of types? This is a surprisingly tricky question
to answer precisely. Instances are driven more by guidelines than rules.
- Conversions must not throw impure exceptions. This means no
undefinedor anything equivalent to it. - Conversions should be unambiguous. If there are multiple reasonable
ways to convert from
atob, then you probably should not add aFrominstance for them. - Conversions should be lossless. If you have
From a bthen no twoavalues should be converted to the samebvalue. - Some conversions necessarily lose information, like converting from a list into a set.
- If you have both
From a bandFrom b a, thenfrom @b @a . from @a @bshould be the same asid. In other words,aandbare isomorphic. - This often true, but not always. For example, converting a list into a set will remove duplicates. And then converting back into a list will put the elements in ascending order.
- If you have both
From a bandFrom b c, then you could also haveFrom a cand it should be the same asfrom @b @c . from @a @b. In other words,Fromis transitive. - This is not always true. For example an
Int8may be represented as a number in JSON, whereas anInt64might be represented as a string. That meansinto @JSON (into @Int64 int8)would not be the same asinto @JSON int8.
In general if s is a t, then you should add a From
instance for it. But if s merely can be a t, then you could add a
TryFrom instance for it. And if it is technically
possible to convert from s to t but there are a lot of caveats, you
probably should not write any instances at all.