witch-1.2.0.1: Convert values from one type into another.
Safe HaskellSafe-Inferred
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

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

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 target means that you can convert from a value of type source 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

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

Instances

Instances details
From Pico DiffTime Source #

Uses realToFrac.

Instance details

Defined in Witch.Instances

Methods

from :: Pico -> DiffTime Source #

From Pico NominalDiffTime Source #

Uses secondsToNominalDiffTime.

Instance details

Defined in Witch.Instances

From Int16 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Int32 Source #

From Int16 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Int64 Source #

From Int16 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Integer Source #

From Int16 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Double Source #

From Int16 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Float Source #

From Int16 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Int Source #

From Int32 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int32 -> Int64 Source #

From Int32 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int32 -> Integer Source #

From Int32 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int32 -> Double Source #

From Int64 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int64 -> Integer Source #

From Int8 Int16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int16 Source #

From Int8 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int32 Source #

From Int8 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int64 Source #

From Int8 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Integer Source #

From Int8 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Double Source #

From Int8 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Float Source #

From Int8 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int Source #

From Rational UniversalTime Source #

Uses ModJulianDate.

Instance details

Defined in Witch.Instances

From Rational TimeOfDay Source #

Uses dayFractionToTimeOfDay.

Instance details

Defined in Witch.Instances

From Rational Double Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

from :: Rational -> Double Source #

From Rational Float Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

from :: Rational -> Float Source #

From Word16 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Int32 Source #

From Word16 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Int64 Source #

From Word16 Word32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Word32 Source #

From Word16 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Word64 Source #

From Word16 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Integer Source #

From Word16 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Natural Source #

From Word16 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Double Source #

From Word16 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Float Source #

From Word16 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Int Source #

From Word16 Word Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Word Source #

From Word32 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Int64 Source #

From Word32 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Word64 Source #

From Word32 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Integer Source #

From Word32 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Natural Source #

From Word32 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Double Source #

From Word64 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word64 -> Integer Source #

From Word64 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word64 -> Natural Source #

From Word8 Int16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int16 Source #

From Word8 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int32 Source #

From Word8 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int64 Source #

From Word8 Word16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word16 Source #

From Word8 Word32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word32 Source #

From Word8 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word64 Source #

From Word8 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Integer Source #

From Word8 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Natural Source #

From Word8 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Double Source #

From Word8 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Float Source #

From Word8 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int Source #

From Word8 Word Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word Source #

From ByteString ByteString Source #

Uses fromStrict.

Instance details

Defined in Witch.Instances

From ByteString ShortByteString Source #

Uses toShort.

Instance details

Defined in Witch.Instances

From ByteString ByteString Source #

Uses toStrict.

Instance details

Defined in Witch.Instances

From ShortByteString ByteString Source #

Uses fromShort.

Instance details

Defined in Witch.Instances

From Text Text Source #

Uses fromStrict.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> Text0 Source #

From Text String Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> String Source #

From Text Text Source #

Uses toStrict.

Instance details

Defined in Witch.Instances

Methods

from :: Text0 -> Text Source #

From Text String Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> String Source #

From CalendarDiffDays CalendarDiffTime Source #

Uses calendarTimeDays.

Instance details

Defined in Witch.Instances

From Day DayOfWeek Source #

Uses dayOfWeek.

Instance details

Defined in Witch.Instances

Methods

from :: Day -> DayOfWeek Source #

From Day Integer Source #

Uses toModifiedJulianDay.

Instance details

Defined in Witch.Instances

Methods

from :: Day -> Integer Source #

From DiffTime Pico Source #

Uses realToFrac.

Instance details

Defined in Witch.Instances

Methods

from :: DiffTime -> Pico Source #

From DiffTime TimeOfDay Source #

Uses timeToTimeOfDay.

Instance details

Defined in Witch.Instances

From NominalDiffTime Pico Source #

Uses nominalDiffTimeToSeconds.

Instance details

Defined in Witch.Instances

From NominalDiffTime CalendarDiffTime Source #

Uses calendarTimeTime.

Instance details

Defined in Witch.Instances

From POSIXTime UTCTime Source #

Uses posixSecondsToUTCTime.

Instance details

Defined in Witch.Instances

From SystemTime AbsoluteTime Source #

Uses systemToTAITime.

Instance details

Defined in Witch.Instances

From SystemTime POSIXTime Source #

Uses systemToPOSIXTime.

Instance details

Defined in Witch.Instances

From SystemTime UTCTime Source #

Uses systemToUTCTime.

Instance details

Defined in Witch.Instances

From UTCTime POSIXTime Source #

Uses utcTimeToPOSIXSeconds.

Instance details

Defined in Witch.Instances

From UTCTime SystemTime Source #

Uses utcToSystemTime.

Instance details

Defined in Witch.Instances

From UniversalTime Rational Source #

Uses getModJulianDate.

Instance details

Defined in Witch.Instances

From TimeOfDay Rational Source #

Uses timeOfDayToDayFraction.

Instance details

Defined in Witch.Instances

From TimeOfDay DiffTime Source #

Uses timeOfDayToTime.

Instance details

Defined in Witch.Instances

From ZonedTime UTCTime Source #

Uses zonedTimeToUTC.

Instance details

Defined in Witch.Instances

From 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

from :: String -> Text Source #

From 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

from :: String -> Text Source #

From Integer Day Source #

Uses ModifiedJulianDay.

Instance details

Defined in Witch.Instances

Methods

from :: Integer -> Day Source #

From Natural Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Natural -> Integer Source #

From Double Float Source #

Uses double2Float. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

from :: Double -> Float Source #

From Float Double Source #

Uses float2Double.

Instance details

Defined in Witch.Instances

Methods

from :: Float -> Double Source #

From Int Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int -> Int64 Source #

From Int Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int -> Integer Source #

From Word Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word -> Word64 Source #

From Word Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word -> Integer Source #

From Word Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word -> Natural Source #

From a a Source #

Uses id.

Instance details

Defined in Witch.Instances

Methods

from :: a -> a Source #

From ByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: ByteString -> [Word8] Source #

From ByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: ByteString -> [Word8] Source #

From ShortByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

From IntSet [Int] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

from :: IntSet -> [Int] Source #

From Text (UTF_16BE ByteString) Source #

Uses encodeUtf16BE.

Instance details

Defined in Witch.Instances

From Text (UTF_16BE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_16LE ByteString) Source #

Uses encodeUtf16LE.

Instance details

Defined in Witch.Instances

From Text (UTF_16LE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_32BE ByteString) Source #

Uses encodeUtf32BE.

Instance details

Defined in Witch.Instances

From Text (UTF_32BE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_32LE ByteString) Source #

Uses encodeUtf32LE.

Instance details

Defined in Witch.Instances

From Text (UTF_32LE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_8 ByteString) Source #

Uses encodeUtf8.

Instance details

Defined in Witch.Instances

From Text (UTF_8 ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_16BE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_16BE ByteString) Source #

Uses encodeUtf16BE.

Instance details

Defined in Witch.Instances

From Text (UTF_16LE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_16LE ByteString) Source #

Uses encodeUtf16LE.

Instance details

Defined in Witch.Instances

From Text (UTF_32BE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_32BE ByteString) Source #

Uses encodeUtf32BE.

Instance details

Defined in Witch.Instances

From Text (UTF_32LE ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_32LE ByteString) Source #

Uses encodeUtf32LE.

Instance details

Defined in Witch.Instances

From Text (UTF_8 ByteString) Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

From Text (UTF_8 ByteString) Source #

Uses encodeUtf8.

Instance details

Defined in Witch.Instances

From String (UTF_16BE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_16BE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_16LE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_16LE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_32BE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_32BE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_32LE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_32LE ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_8 ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String (UTF_8 ByteString) Source #

Converts via Text.

Instance details

Defined in Witch.Instances

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

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

Instance details

Defined in Witch.Instances

Methods

from :: a -> Complex a Source #

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

Uses (%) with a denominator of 1.

Instance details

Defined in Witch.Instances

Methods

from :: a -> Ratio a Source #

From Integer (Fixed a) Source #

Uses MkFixed. This means from @Integer @Centi 2 is 0.02 rather than 2.00.

Instance details

Defined in Witch.Instances

Methods

from :: Integer -> Fixed a Source #

From a (Tagged t a) Source #

Uses coerce. Essentially the same as Tagged.

Instance details

Defined in Witch.Instances

Methods

from :: a -> Tagged t a Source #

From (ISO_8859_1 ByteString) Text Source #

Uses decodeLatin1.

Instance details

Defined in Witch.Instances

From (ISO_8859_1 ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From (ISO_8859_1 ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From (ISO_8859_1 ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From (ISO_8859_1 ByteString) Text Source #

Uses decodeLatin1.

Instance details

Defined in Witch.Instances

From (ISO_8859_1 ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From [Word8] ByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Methods

from :: [Word8] -> ByteString Source #

From [Word8] ByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Methods

from :: [Word8] -> ByteString Source #

From [Word8] ShortByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

From [Int] IntSet Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

from :: [Int] -> IntSet Source #

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

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

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

From (Seq a) [a] Source #

Uses toList.

Instance details

Defined in Witch.Instances

Methods

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

From (Set a) [a] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

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

From (NonEmpty a) [a] Source #

Uses toList.

Instance details

Defined in Witch.Instances

Methods

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

From [(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

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

From [a] (Seq a) Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

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

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

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

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

Ord k => From [(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

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

HasResolution a => From (Fixed a) Rational Source #

Uses toRational.

Instance details

Defined in Witch.Instances

Methods

from :: Fixed a -> Rational Source #

From (Fixed a) Integer Source #

Uses MkFixed. This means from @Centi @Integer 3.00 is 300 rather than 3.

Instance details

Defined in Witch.Instances

Methods

from :: Fixed a -> Integer Source #

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

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

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

From (TryFromException source oldTarget) (TryFromException source newTarget) Source #

Uses coerce.

Instance details

Defined in Witch.Instances

Methods

from :: TryFromException source oldTarget -> TryFromException source newTarget Source #

From (Tagged t a) a Source #

Uses coerce. Essentially the same as unTagged.

Instance details

Defined in Witch.Instances

Methods

from :: Tagged t a -> a Source #

From (Tagged t a) (Tagged u a) Source #

Uses coerce. Essentially the same as retag.

Instance details

Defined in Witch.Instances

Methods

from :: Tagged t a -> Tagged u a Source #

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 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 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

Instances details
TryFrom Int16 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int16 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int16 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int16 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int16 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int16 Natural Source #

Uses fromIntegral when the input is not negative.

Instance details

Defined in Witch.Instances

TryFrom Int16 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Natural Source #

Uses fromIntegral when the input is not negative.

Instance details

Defined in Witch.Instances

TryFrom Int32 Float Source #

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

Instance details

Defined in Witch.Instances

TryFrom Int32 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int32 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Natural Source #

Uses fromIntegral when the input is not negative.

Instance details

Defined in Witch.Instances

TryFrom 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

TryFrom Int64 Float Source #

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

Instance details

Defined in Witch.Instances

TryFrom Int64 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int64 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int8 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int8 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int8 Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int8 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int8 Natural Source #

Uses fromIntegral when the input is not negative.

Instance details

Defined in Witch.Instances

TryFrom Int8 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word16 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word16 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word16 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Float Source #

Uses fromIntegral when the input is less than or equal to 16,777,215.

Instance details

Defined in Witch.Instances

TryFrom Word32 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word32 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Double Source #

Uses fromIntegral when the input is less than or equal to 9,007,199,254,740,991.

Instance details

Defined in Witch.Instances

TryFrom Word64 Float Source #

Uses fromIntegral when the input is less than or equal to 16,777,215.

Instance details

Defined in Witch.Instances

TryFrom Word64 Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word64 Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word8 Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Natural Source #

Uses fromInteger when the input is not negative.

Instance details

Defined in Witch.Instances

TryFrom 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

TryFrom Integer Float Source #

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

Instance details

Defined in Witch.Instances

TryFrom Integer Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Integer Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Double Source #

Uses fromIntegral when the input is less than or equal to 9,007,199,254,740,991.

Instance details

Defined in Witch.Instances

TryFrom Natural Float Source #

Uses fromIntegral when the input is less than or equal to 16,777,215.

Instance details

Defined in Witch.Instances

TryFrom Natural Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Natural Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Double Int16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Int32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Int64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Int8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Rational Source #

Uses floatToDigits when the input is not NaN or infinity.

Instance details

Defined in Witch.Instances

TryFrom Double Word16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Word32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Word64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Word8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom 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

TryFrom Double Natural Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Int Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Double Word Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Int16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Int32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Int64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Int8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Rational Source #

Uses floatToDigits when the input is not NaN or infinity.

Instance details

Defined in Witch.Instances

TryFrom Float Word16 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Word32 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Word64 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Word8 Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom 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

TryFrom Float Natural Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Int Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Float Word Source #

Converts via Integer.

Instance details

Defined in Witch.Instances

TryFrom Int Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Word64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Int Natural Source #

Uses fromIntegral when the input is not negative.

Instance details

Defined in Witch.Instances

TryFrom 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

TryFrom Int Float Source #

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

Instance details

Defined in Witch.Instances

TryFrom Int Word Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Int16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Int32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Int64 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Int8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Word16 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Word32 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Word8 Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Word Double Source #

Uses fromIntegral when the input is less than or equal to 9,007,199,254,740,991.

Instance details

Defined in Witch.Instances

TryFrom Word Float Source #

Uses fromIntegral when the input is less than or equal to 16,777,215.

Instance details

Defined in Witch.Instances

TryFrom Word Int Source #

Uses toIntegralSized.

Instance details

Defined in Witch.Instances

TryFrom Text (ISO_8859_1 ByteString) Source #

Converts via String.

Instance details

Defined in Witch.Instances

TryFrom Text (ISO_8859_1 ByteString) Source #

Converts via String.

Instance details

Defined in Witch.Instances

TryFrom Text (ISO_8859_1 ByteString) Source #

Converts via String.

Instance details

Defined in Witch.Instances

TryFrom Text (ISO_8859_1 ByteString) Source #

Converts via String.

Instance details

Defined in Witch.Instances

TryFrom String (ISO_8859_1 ByteString) Source #

Uses pack when each character isLatin1.

Instance details

Defined in Witch.Instances

TryFrom String (ISO_8859_1 ByteString) Source #

Uses pack when each character isLatin1.

Instance details

Defined in Witch.Instances

HasResolution a => TryFrom Rational (Fixed a) Source #

Uses fromRational as long as there isn't a loss of precision.

Instance details

Defined in Witch.Instances

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

Uses realPart when the imaginary part is 0.

Instance details

Defined in Witch.Instances

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

Uses numerator when the denominator is 1.

Instance details

Defined in Witch.Instances

Methods

tryFrom :: Ratio a -> Either (TryFromException (Ratio a) a) a Source #

TryFrom (UTF_16BE ByteString) Text Source #

Uses decodeUtf16BE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16BE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16BE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16BE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16BE ByteString) Text Source #

Uses decodeUtf16BE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16BE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16LE ByteString) Text Source #

Uses decodeUtf16LE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16LE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16LE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16LE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16LE ByteString) Text Source #

Uses decodeUtf16LE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_16LE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32BE ByteString) Text Source #

Uses decodeUtf32BE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32BE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32BE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32BE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32BE ByteString) Text Source #

Uses decodeUtf32BE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32BE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32LE ByteString) Text Source #

Uses decodeUtf32LE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32LE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32LE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32LE ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32LE ByteString) Text Source #

Uses decodeUtf32LE.

Instance details

Defined in Witch.Instances

TryFrom (UTF_32LE ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_8 ByteString) Text Source #

Uses decodeUtf8'.

Instance details

Defined in Witch.Instances

TryFrom (UTF_8 ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_8 ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_8 ByteString) Text Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom (UTF_8 ByteString) Text Source #

Uses decodeUtf8'.

Instance details

Defined in Witch.Instances

TryFrom (UTF_8 ByteString) String Source #

Converts via Text.

Instance details

Defined in Witch.Instances

TryFrom [a] (NonEmpty a) Source #

Uses nonEmpty.

Instance details

Defined in Witch.Instances

Methods

tryFrom :: [a] -> Either (TryFromException [a] (NonEmpty a)) (NonEmpty a) Source #

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

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

Defined in Witch.TryFromException

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

Defined in 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 coerce.

Instance details

Defined in Witch.Instances

Methods

from :: TryFromException source oldTarget -> TryFromException source newTarget Source #

Encodings

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 @u

maybeTryFrom :: (source -> Maybe target) -> source -> Either (TryFromException source target) target Source #

This function can be used to implement tryFrom with a function that returns Maybe. For example:

-- Avoid this:
tryFrom s = case f s of
  Nothing -> Left $ TryFromException s Nothing
  Just t -> Right t

-- Prefer this:
tryFrom = maybeTryFrom f

eitherTryFrom :: Exception exception => (source -> Either exception target) -> source -> Either (TryFromException source target) target Source #

This function can be used to implement tryFrom with a function that returns Either. For example:

-- Avoid this:
tryFrom s = case f s of
  Left e -> Left . TryFromException s . Just $ toException e
  Right t -> Right t

-- Prefer this:
tryFrom = eitherTryFrom f

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 m. (TryFrom source target, Lift target, Show source, Typeable source, Typeable target, Quote m) => source -> Code m 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 m. (TryFrom source target, Lift target, Show source, Typeable source, Typeable target, Quote m) => source -> Code m 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")

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 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 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 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 From instance for them.
  • Conversions should be lossless. If you have From a b then no two a values should be converted to the same b value.

    • Some conversions necessarily lose information, like converting from a list into a set.
  • If you have both From a b and From b a, then from @b @a . from @a @b should be the same as id. In other words, a and b are 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 b and From b c, then you could also have From a c and it should be the same as from @b @c . from @a @b. In other words, From is transitive.

    • This is not always true. For example an Int8 may be represented as a number in JSON, whereas an Int64 might be represented as a string. That means into @JSON (into @Int64 int8) would not be the same as into @JSON int8.
  • You should not have both a From instance and a TryFrom instance for the same pair of types.
  • If you have a From or TryFrom instance for a pair of types, then you should probably have a From or TryFrom instance for the same pair of types but in the opposite direction. In other words if you have From a b then you should have From b a or TryFrom 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 s is more useful that From String s. The former says that the type s is the same as a string literal, but the latter just says you can produce a value of type s when given a string.
  • The From type class works great for specific pairs of types, but can get confusing when it's polymorphic. For example if you have some function with a From s t constraint, that doesn't really tell you anything about what it's doing.