witch-0.1.1.0: Convert values from one type into another.
Safe HaskellNone
LanguageHaskell2010

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
Synopsis

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 Cast type class is for conversions that cannot fail, and the TryCast 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 for newtypes, but it does not work for converting between arbitrary types like Int8 and 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 basement package, 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.pack are 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 toEnum are more convenient but may have unwanted semantics or runtime behavior. For example the Enum type class is more or less tied to the Int data type and frequently throws impure exceptions.
  • Polymorphic conversion functions like fromIntegral are 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 negative Int into a Word will overflow, which may be surprising.

Instances

When should you add a Cast (or TryCast) 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 undefined or anything equivalent to it.
  • Conversions should be unambiguous. If there are multiple reasonable ways to convert from a to b, then you probably should not add a Cast instance for them.
  • Conversions should be lossless. If you have Cast a b then no two a values should be converted to the same b value.
  • If you have both Cast a b and Cast b a, then cast @b @a . cast @a @b should be the same as id. In other words, a and b are isomorphic.
  • If you have both Cast a b and Cast b c, then you could also have Cast a c and it should be the same as cast @b @c . cast @a @b. In other words, Cast is transitive.

In general if s is a t, then you should add a Cast instance for it. But if s merely can be a t, then you could add a TryCast 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.

Type applications

This library is designed to be used with the TypeApplications language extension. Although it is not required for basic functionality, it is strongly encouraged. You can use cast, tryCast, unsafeCast, and liftedCast without type applications. Everything else requires a type application.

Ambiguous types

You may see Identity show up in some type signatures. Anywhere you see Identity a, you can mentally replace it with a. It is a type family used to trick GHC into requiring type applications for certain functions. If you forget to give a type application, you will see an error like this:

>>> from (1 :: Int8) :: Int16
<interactive>:1:1: error:
    * Couldn't match type `Identity s0' with `Int8'
        arising from a use of `from'
      The type variable `s0' is ambiguous
    * In the expression: from (1 :: Int8) :: Int16
      In an equation for `it': it = from (1 :: Int8) :: Int16

You can fix the problem by giving a type application:

>>> from @Int8 1 :: Int16
1

Type classes

Cast

class Cast source target where Source #

This type class is for converting values from some source type into some other target type. The constraint Cast source target measn that you can convert from a value of type source into a value of type target.

This type class is for conversions that cannot fail. If your conversion can fail, consider implementing TryCast instead.

Minimal complete definition

Nothing

Methods

cast :: source -> target Source #

This method implements the conversion of a value between types. At call sites you will usually want to use from or 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 Cast Name String
>>> instance Cast String Name

default cast :: Coercible source target => source -> target Source #

Instances

Instances details
Cast Double Float Source #

Uses realToFrac. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

cast :: Double -> Float Source #

Cast Float Double Source #

Uses realToFrac.

Instance details

Defined in Witch.Instances

Methods

cast :: Float -> Double Source #

Cast Int Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int -> Int64 Source #

Cast Int Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int -> Integer Source #

Cast Int8 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Double Source #

Cast Int8 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Float Source #

Cast Int8 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Int Source #

Cast Int8 Int16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Int16 Source #

Cast Int8 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Int32 Source #

Cast Int8 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Int64 Source #

Cast Int8 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int8 -> Integer Source #

Cast Int16 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int16 -> Double Source #

Cast Int16 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int16 -> Float Source #

Cast Int16 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int16 -> Int Source #

Cast Int16 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int16 -> Int32 Source #

Cast Int16 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int16 -> Int64 Source #

Cast Int16 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int16 -> Integer Source #

Cast Int32 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int32 -> Double Source #

Cast Int32 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int32 -> Int64 Source #

Cast Int32 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int32 -> Integer Source #

Cast Int64 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Int64 -> Integer Source #

Cast Natural Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Natural -> Integer Source #

Cast Rational Double Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

cast :: Rational -> Double Source #

Cast Rational Float Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

cast :: Rational -> Float Source #

Cast Word Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word -> Integer Source #

Cast Word Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word -> Natural Source #

Cast Word Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word -> Word64 Source #

Cast Word8 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Double Source #

Cast Word8 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Float Source #

Cast Word8 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Int Source #

Cast Word8 Int16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Int16 Source #

Cast Word8 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Int32 Source #

Cast Word8 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Int64 Source #

Cast Word8 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Integer Source #

Cast Word8 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Natural Source #

Cast Word8 Word Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Word Source #

Cast Word8 Word16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Word16 Source #

Cast Word8 Word32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Word32 Source #

Cast Word8 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word8 -> Word64 Source #

Cast Word16 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Double Source #

Cast Word16 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Float Source #

Cast Word16 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Int Source #

Cast Word16 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Int32 Source #

Cast Word16 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Int64 Source #

Cast Word16 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Integer Source #

Cast Word16 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Natural Source #

Cast Word16 Word Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Word Source #

Cast Word16 Word32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Word32 Source #

Cast Word16 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word16 -> Word64 Source #

Cast Word32 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word32 -> Double Source #

Cast Word32 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word32 -> Int64 Source #

Cast Word32 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word32 -> Integer Source #

Cast Word32 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word32 -> Natural Source #

Cast Word32 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word32 -> Word64 Source #

Cast Word64 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word64 -> Integer Source #

Cast Word64 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

cast :: Word64 -> Natural Source #

Cast String Text Source #

Uses pack. Some Char values cannot be represented in Text and will be replaced with '\xFFFD'.

Instance details

Defined in Witch.Instances

Methods

cast :: String -> Text Source #

Cast String Text Source #

Uses pack. Some Char values cannot be represented in Text and will be replaced with '\xFFFD'.

Instance details

Defined in Witch.Instances

Methods

cast :: String -> Text Source #

Cast ShortByteString ByteString Source #

Uses fromShort.

Instance details

Defined in Witch.Instances

Cast ByteString ByteString Source #

Uses toStrict.

Instance details

Defined in Witch.Instances

Cast ByteString ShortByteString Source #

Uses toShort.

Instance details

Defined in Witch.Instances

Cast ByteString ByteString Source #

Uses fromStrict.

Instance details

Defined in Witch.Instances

Cast Text String Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

cast :: Text -> String Source #

Cast Text ByteString Source #

Uses encodeUtf8.

Instance details

Defined in Witch.Instances

Methods

cast :: Text -> ByteString Source #

Cast Text Text Source #

Uses toStrict.

Instance details

Defined in Witch.Instances

Methods

cast :: Text0 -> Text Source #

Cast Text String Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

cast :: Text -> String Source #

Cast Text ByteString Source #

Uses encodeUtf8.

Instance details

Defined in Witch.Instances

Methods

cast :: Text -> ByteString Source #

Cast Text Text Source #

Uses fromStrict.

Instance details

Defined in Witch.Instances

Methods

cast :: Text -> Text0 Source #

Num a => Cast a (Complex a) Source #

Uses (:+) with an imaginary part of 0.

Instance details

Defined in Witch.Instances

Methods

cast :: a -> Complex a Source #

Integral a => Cast a (Ratio a) Source #

Uses (%) with a denominator of 1.

Instance details

Defined in Witch.Instances

Methods

cast :: a -> Ratio a Source #

Cast ShortByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Cast ByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

cast :: ByteString -> [Word8] Source #

Cast ByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

cast :: ByteString -> [Word8] Source #

Cast IntSet [Int] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

cast :: IntSet -> [Int] Source #

Cast Integer (Fixed a) Source #

Uses MkFixed. This means cast 2 :: Centi is 0.02 rather than 2.00.

Instance details

Defined in Witch.Instances

Methods

cast :: Integer -> Fixed a Source #

Cast [Int] IntSet Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

cast :: [Int] -> IntSet Source #

Cast [Word8] ShortByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Cast [Word8] ByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Methods

cast :: [Word8] -> ByteString Source #

Cast [Word8] ByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Methods

cast :: [Word8] -> ByteString Source #

Cast [(Int, v)] (IntMap v) Source #

Uses fromList. If there are duplicate keys, later values will overwrite earlier ones.

Instance details

Defined in Witch.Instances

Methods

cast :: [(Int, v)] -> IntMap v Source #

Cast [a] (Seq a) Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

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

Ord a => Cast [a] (Set a) Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

cast :: [a] -> Set a Source #

Cast (NonEmpty a) [a] Source #

Uses toList.

Instance details

Defined in Witch.Instances

Methods

cast :: NonEmpty a -> [a] Source #

Cast (IntMap v) [(Int, v)] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

cast :: IntMap v -> [(Int, v)] Source #

Cast (Seq a) [a] Source #

Uses toList.

Instance details

Defined in Witch.Instances

Methods

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

Cast (Set a) [a] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

cast :: Set a -> [a] Source #

Ord k => Cast [(k, v)] (Map k v) Source #

Uses fromList. If there are duplicate keys, later values will overwrite earlier ones.

Instance details

Defined in Witch.Instances

Methods

cast :: [(k, v)] -> Map k v Source #

Cast (Fixed a) Integer Source #

Uses MkFixed. This means cast (3.00 :: Centi) is 300 rather than 3.

Instance details

Defined in Witch.Instances

Methods

cast :: Fixed a -> Integer Source #

Cast (Map k v) [(k, v)] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

cast :: Map k v -> [(k, v)] Source #

Cast (TryCastException s t0) (TryCastException s t1) Source # 
Instance details

Defined in Witch.Instances

from :: forall s target source. (Identity s ~ source, Cast source target) => source -> target Source #

This is the same as cast except that it requires a type application for the source type.

-- Avoid this:
cast (x :: s)

-- Prefer this:
from @s x

into :: forall t source target. (Identity t ~ target, Cast source target) => source -> target Source #

This is the same as cast except that it requires a type application for the target type.

-- Avoid this:
cast x :: t

-- Prefer this:
into @t x

TryCast

class TryCast source target where Source #

This type class is for converting values from some source type into some other target type. The constraint TryCast source target means that you may be able to convert from a value of type source 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 Cast instead.

Methods

tryCast :: source -> Either (TryCastException source target) target Source #

This method implements the conversion of a value between types. At call sites you will usually want to use tryFrom or tryInto instead of this method.

Instances

Instances details
TryCast Double Int Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Int8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Int16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Int32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Int64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Integer Source #

Converts via Rational when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Double Natural Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Rational Source #

Uses toRational when the input is not NaN or infinity.

Instance details

Defined in Witch.Instances

TryCast Double Word Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Word8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Word16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Word32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Double Word64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Int Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Int8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Int16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Int32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Int64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Integer Source #

Converts via Rational when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Float Natural Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Rational Source #

Uses toRational when the input is not NaN or infinity.

Instance details

Defined in Witch.Instances

TryCast Float Word Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Word8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Word16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Word32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Float Word64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryCast Int Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Int Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Int Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

Defined in Witch.Instances

TryCast Int Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int8 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

Defined in Witch.Instances

TryCast Int8 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int8 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int8 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int8 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int8 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int16 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int16 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

Defined in Witch.Instances

TryCast Int16 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int16 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int16 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int16 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int16 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Int32 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

Defined in Witch.Instances

TryCast Int32 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int32 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Int64 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Int64 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

Defined in Witch.Instances

TryCast Int64 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Int64 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Integer Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Integer Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Natural Source #

Uses fromInteger when the input is non-negative.

Instance details

Defined in Witch.Instances

TryCast Integer Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Integer Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Natural Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Natural Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Natural Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Word Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Word Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word8 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word16 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word16 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word16 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Word32 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word32 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

Defined in Witch.Instances

TryCast Word64 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

Defined in Witch.Instances

TryCast Word64 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast Word64 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryCast ByteString Text Source #

Uses decodeUtf8'.

Instance details

Defined in Witch.Instances

TryCast ByteString Text Source #

Uses decodeUtf8'.

Instance details

Defined in Witch.Instances

(Eq a, Num a) => TryCast (Ratio a) a Source #

Uses numerator when the denominator is 1.

Instance details

Defined in Witch.Instances

Methods

tryCast :: Ratio a -> Either (TryCastException (Ratio a) a) a Source #

(Eq a, Num a) => TryCast (Complex a) a Source #

Uses realPart when the imaginary part is 0.

Instance details

Defined in Witch.Instances

TryCast [a] (NonEmpty a) Source #

Uses nonEmpty.

Instance details

Defined in Witch.Instances

Methods

tryCast :: [a] -> Either (TryCastException [a] (NonEmpty a)) (NonEmpty a) Source #

tryFrom :: forall s target source. (Identity s ~ source, TryCast source target) => source -> Either (TryCastException source target) target Source #

This is the same as tryCast except that it requires a type application for the source type.

-- Avoid this:
tryCast (x :: s)

-- Prefer this:
tryFrom @s x

tryInto :: forall t source target. (Identity t ~ target, TryCast source target) => source -> Either (TryCastException source target) target Source #

This is the same as tryCast except that it requires a type application for the target type.

-- Avoid this:
tryCast x :: Either (TryCastException s t) t

-- Prefer this:
tryInto @t x

newtype TryCastException source target Source #

This exception is thrown when a TryCast conversion fails. It has the original source value that caused the failure and it knows the target type it was trying to convert into.

Constructors

TryCastException source 

Instances

Instances details
Eq source => Eq (TryCastException source target) Source # 
Instance details

Defined in Witch.TryCastException

Methods

(==) :: TryCastException source target -> TryCastException source target -> Bool #

(/=) :: TryCastException source target -> TryCastException source target -> Bool #

(Show source, Typeable source, Typeable target) => Show (TryCastException source target) Source # 
Instance details

Defined in Witch.TryCastException

Methods

showsPrec :: Int -> TryCastException source target -> ShowS #

show :: TryCastException source target -> String #

showList :: [TryCastException source target] -> ShowS #

(Show source, Typeable source, Typeable target) => Exception (TryCastException source target) Source # 
Instance details

Defined in Witch.TryCastException

Cast (TryCastException s t0) (TryCastException s t1) Source # 
Instance details

Defined in Witch.Instances

Utilities

as :: forall s source. Identity s ~ source => source -> source Source #

This is the same as id except that it requires a type application. 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 t source target. (Identity t ~ target, Cast source target, Cast 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 . from @s

-- Prefer this:
over @t f

via :: forall u source target through. (Identity u ~ through, Cast source through, Cast 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 Cast 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 u source target through. (Identity u ~ through, TryCast source through, TryCast through target) => source -> Either (TryCastException source target) target Source #

This is similar to via except that it works with TryCast instances instead. This function is especially convenient because juggling the types in the TryCastException can be tedious.

-- Avoid this:
fmap (tryFrom @u) . tryInto @u

-- Prefer this:
tryVia @u

Unsafe

unsafeCast :: forall source target. (HasCallStack, TryCast source target, Show source, Typeable source, Typeable target) => source -> target Source #

This function is like tryCast except that it will throw an impure exception if the conversion fails.

-- Avoid this:
either throw id . cast

-- Prefer this:
unsafeCast

unsafeFrom :: forall s target source. (Identity s ~ source, HasCallStack, TryCast source target, Show source, Typeable source, Typeable target) => source -> target Source #

This function is like from except that it will throw an impure exception if the conversion fails.

-- Avoid this:
either throw id . from @s

-- Prefer this:
unsafeFrom @s

unsafeInto :: forall t source target. (Identity t ~ target, HasCallStack, TryCast source target, Show source, Typeable source, Typeable target) => source -> target Source #

This function is like into except that it will throw an impure exception if the conversion fails.

-- Avoid this:
either throw id . into @t

-- Prefer this:
unsafeInto @t

Template Haskell

liftedCast :: forall source target. (TryCast source target, Lift target, Show source, Typeable source, Typeable target) => source -> Q (TExp target) Source #

This is like unsafeCast except that it works at compile time rather than runtime.

-- Avoid this:
unsafeCast "some literal"

-- Prefer this:
$$(liftedCast "some literal")

liftedFrom :: forall s target source. (Identity s ~ source, TryCast 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 t source target. (Identity t ~ target, TryCast 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")