| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Functora.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, the functions that you will use most often are
 into for conversions that always succeed and
 tryInto for conversions that sometimes fail.
Please consider reading the blog post that announces this library: https://taylor.fausak.me/2021/07/13/witch/
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
- data TryFromException source target = TryFromException source (Maybe SomeException)
- type ISO_8859_1 = Tagged "ISO-8859-1"
- type UTF_8 = Tagged "UTF-8"
- type UTF_16LE = Tagged "UTF-16LE"
- type UTF_16BE = Tagged "UTF-16BE"
- type UTF_32LE = Tagged "UTF-32LE"
- type UTF_32BE = Tagged "UTF-32BE"
- 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
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 From source targetsource into a value of type
 target.
This type class is for conversions that always succeed. If your conversion
 sometimes fails, 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 may prefer to use into instead.
-- Avoid this: from (x :: s) -- Prefer this (using [@TypeApplications@](https://downloads.haskell.org/ghc/9.6.1/docs/users_guide/exts/type_applications.html) language extension): from @s x
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 TryFrom source targetsource into a value
 of type target, but that conversion may fail at runtime.
This type class is for conversions that can sometimes fail. If your
 conversion always succeeds, 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 may want to use tryInto instead.
-- Avoid this: tryFrom (x :: s) -- Prefer this: tryFrom @s
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
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) => Exception (TryFromException source target) Source # | |
| Defined in Functora.Witch.TryFromException Methods toException :: TryFromException source target -> SomeException # fromException :: SomeException -> Maybe (TryFromException source target) # displayException :: TryFromException source target -> String # | |
| (Show source, Typeable source, Typeable target) => Show (TryFromException source target) Source # | |
| Defined in Functora.Witch.TryFromException Methods showsPrec :: Int -> TryFromException source target -> ShowS # show :: TryFromException source target -> String # showList :: [TryFromException source target] -> ShowS # | |
| From (TryFromException source oldTarget) (TryFromException source newTarget) Source # | Uses  | 
| Defined in Functora.Witch.Instances Methods from :: TryFromException source oldTarget -> TryFromException source newTarget Source # | |
Encodings
type ISO_8859_1 = Tagged "ISO-8859-1" Source #
Utilities
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 (TryFromException _ e) -> Left $ TryFromException x e
  Right y -> case tryFrom @u y of
    Left (TryFromException _ e) -> Left $ TryFromException x e
    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
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.
Type applications
Although you can use this library without the TypeApplications
 language extension, the extension is strongly recommended. Since most
 functions provided by this library are polymorphic in at least one type
 variable, it's easy to use them in a situation that would be ambiguous.
 Normally you could resolve the ambiguity with an explicit type signature,
 but type applications are much more ergonomic. For example:
-- Avoid this: f . (from :: Int8 -> Int16) . g -- Prefer this: f . from @Int8 @Int16 . g
Most functions in this library have two versions with their type variables in opposite orders. That's because usually one side of the conversion or the other already has its type inferred by context. In those situations it makes sense to only provide one type argument.
-- Avoid this: (assuming f :: Int16 -> ...) f $ from @Int8 @Int16 0 -- Prefer this: f $ from @Int8 0
-- Avoid this: (assuming x :: Int8) g $ from @Int8 @Int16 x -- Prefer this: g $ into @Int16 x
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 for- newtypes, but it does not work for converting between arbitrary types like- Int8and- Int16.
- 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 the- basementpackage, 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 two- avalues should be converted to the same- bvalue.- Some conversions necessarily lose information, like converting from a list into a set.
 
- If you have both - From a band- From b a, then- from @b @a . from @a @bshould be the same as- id. In other words,- aand- bare 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 band- From b c, then you could also have- From a cand it should be the same as- from @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.
 
- This is not always true. For example an 
- You should not have both a Frominstance and aTryFrominstance for the same pair of types.
- If you have a FromorTryFrominstance for a pair of types, then you should probably have aFromorTryFrominstance for the same pair of types but in the opposite direction. In other words if you haveFrom a bthen you should haveFrom b aorTryFrom b a.
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.
Laws
As the previous section notes, there aren't any cut and dried laws for
 the From and TryFrom type classes. However it can be useful to
 consider the following equations for guiding instances:
-- same strictness seq (from @a @b x) y = seq x y seq (tryFrom @a @b x) y = seq x y
-- round trip from @b @a (from @a @b x) = x
-- transitive from @b @c (from @a @b x) = from @a @c x tryFrom @b @a (from @a @b x) = Right x if isRight (tryFrom @a @b x) then fmap (from @b @a) (tryFrom @a @b x) = Right x if isRight (tryFrom @a @b x) then do fmap (tryFrom @b @a) (tryFrom @a @b x) = Right (Right x)
Integral types
There are a lot of types that represent various different ranges of
 integers, and Witch may not provide the instances you want. In particular
 it does not provide a total way to convert from an Int32 into an Int.
 Why is that?
The Haskell Language Report only demands that Ints have at least 30
 bits of precision. That means a reasonable Haskell implementation could
 have an Int type that's smaller than the Int32 type.
However in practice everyone uses the same Haskell implementation: GHC.
 And with GHC the Int type always has 32 bits of precision, even on
 32-bit architectures. So for almost everybody, it's probably safe to use
 unsafeFrom @Int32 @Int. Similarly most software these days runs on
 machines with 64-bit architectures. That means it's also probably safe
 for you to use unsafeFrom @Int64 @Int.
All of the above also applies for Word, Word32, and Word64.
Downsides
As the author of this library, I obviously think that everyone should use it because it's the greatest thing since sliced bread. But nothing is perfect, so what are some downsides to this library?
- More specific type classes are often better. For example, IsString sis more useful thatFrom String s. The former says that the typesis the same as a string literal, but the latter just says you can produce a value of typeswhen given a string.
- The Fromtype class works great for specific pairs of types, but can get confusing when it's polymorphic. For example if you have some function with aFrom s tconstraint, that doesn't really tell you anything about what it's doing.