| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Witch
Description
This module provides the Cast type class for converting values between
various types. This aims to be a common interface for the various xToY or
yFromX functions you might write instead. It is inspired by the
std::convert::From trait that the Rust programming language provides.
Many Haskell libraries already provide similar functionality. Here's how this module compares to them:
- https://hackage.haskell.org/package/base-4.14.0.0/docs/Data-Coerce.html: This type class is convenient because it's automatically inferred by the compiler, but it only works for types that have the same runtime representation.
- https://hackage.haskell.org/package/convertible-1.1.1.0/docs/Data-Convertible-Base.html: This type class allows for conversions to fail.
- https://hackage.haskell.org/package/basement-0.0.11/docs/Basement-From.html:
This type class is essentially the same, but the
basementpackage is an alternative standard library that some people may not want to depend on. - https://hackage.haskell.org/package/inj-base-0.2.0.0/docs/Inj-Base.html: This type class requires conversions to be injective, as opposed to merely suggesting it. Also some conversions fail at runtime.
- https://github.com/mbj/conversions/blob/6ac6c52/src/Data/Conversions/FromType.hs: This type class comes with many convenient helper functions, but some of the provided instances fail at runtime.
- https://github.com/kframework/kore/blob/626f230/kore/src/From.hs: This package is not available on Hackage, but otherwise is very similar to this one.
Synopsis
- class Cast source target where
- cast :: source -> target
- from :: forall s target source. (Ambiguous s ~ source, Cast source target) => source -> target
- into :: forall t source target. (Ambiguous t ~ target, Cast source target) => source -> target
- via :: forall through source target. (Cast source through, Cast through target) => source -> target
Documentation
class Cast source target where Source #
This type class represents a way to convert values from some type into
another type. The constraint Cast a b means that you can convert from a
value of type a into a value of type b.
This is primarily intended for "zero cost" conversions like newtypes. For
example if you wanted to have a type to represent someone's name, you could
say:
newtype Name = Name String instance Cast String Name instance Cast Name String
And then you could convert back and forth between Names and Strings:
let someString = "Taylor" let someName = Name someString into @Name someString -- convert from string to name into @String someName -- convert from name to string
This type class does not have any laws, but it does have some expectations:
- Conversions should be total. A conversion should never fail or crash.
Avoid writing instances like
Cast Int (Maybe Char). (It might be worthwhile to have a separateTryCasttype class for this.) - Conversions should be unambiguous. For example there are many ways to
decode a
ByteStringintoText, so you shouldn't provide an instance for that. - Conversions should be cheap, ideally free. For example converting from
StringtoTextis probably fine, but converting from a UTF-8 encodedByteStringtoTextis problematic. - Conversions should be lossless. In other words if you have
Cast a bthen no twoavalues should be converted to the samebvalue. For exampleCast Int Integeris fine because everyIntcan be mapped to a correspondingInteger, butCast Integer Intis not good because someIntegers are out of bounds and would need to be clamped. - If you have both
Cast a bandCast b a, thencast . castshould be the same asid. In other wordsaandbare isomorphic. - If you have both
Cast a bandCast b c, then it's up to you if you want to provideCast a c. Sometimes usingviais ergonomic enough, other times you want the extra instance. (It would be nice if we could provideinstance (Cast a b, Cast b c) => Cast a c where cast = via @b.)
Minimal complete definition
Nothing
Methods
cast :: source -> target Source #
This method implements the conversion of a value between types. In
practice most instances don't need an explicit implementation. At call
sites you'll usually want to use from or into instead of cast.
The default implementation of cast simply calls coerce, which
works for types that have the same runtime representation.
Instances
from :: forall s target source. (Ambiguous s ~ source, Cast source target) => source -> target Source #
This function converts a value from one type into another. This is
intended to be used with the TypeApplications language extension. The
Ambiguous type in the signature makes a type application required. If
you'd prefer not to provide a type application, use cast instead.
As an example, here are a few ways to convert from an Int into an
Integer:
from @Int @Integer 123 from @_ @Integer (123 :: Int) from @Int @_ 123 :: Integer from @Int 123 :: Integer
Often the context around an expression will make the explicit type
signatures unnecessary. If you find yourself using a partial type
signature, consider using into instead. For example:
let someInt = 123 :: Int from @_ @Integer someInt -- avoid this into @Integer someInt -- prefer this
into :: forall t source target. (Ambiguous t ~ target, Cast source target) => source -> target Source #
This function converts a value from one type into another. This is the
same as from except that the type variables are in the opposite order.
via :: forall through source target. (Cast source through, Cast through target) => source -> target Source #
This function converts a value from one type into another by going through
some third type. This is the same as calling cast (or from or into)
twice, but can sometimes be more convenient.
Note that the type in the middle of the conversion is the first type
variable of this function. In other words, via @b @a @c first converts
from a to b, and then from b to c. Often both a and c will be
inferred from context, which means you can just write via @b.