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

Witch

Description

This module provides the Cast type class for converting values between various types. This aims to be a common interface for the various xToY or yFromX functions you might write instead. It is inspired by the std::convert::From trait that the Rust programming language provides.

Many Haskell libraries already provide similar functionality. Here's how this module compares to them:

Synopsis
  • class Cast source target where
    • cast :: source -> target
  • from :: forall s target source. (Ambiguous s ~ source, Cast source target) => source -> target
  • into :: forall t source target. (Ambiguous t ~ target, Cast source target) => source -> target
  • via :: forall through source target. (Cast source through, Cast through target) => source -> target

Documentation

class Cast source target where Source #

This type class represents a way to convert values from some type into another type. The constraint Cast a b means that you can convert from a value of type a into a value of type b.

This is primarily intended for "zero cost" conversions like newtypes. For example if you wanted to have a type to represent someone's name, you could say:

newtype Name = Name String
instance Cast String Name
instance Cast Name String

And then you could convert back and forth between Names and Strings:

let someString = "Taylor"
let someName = Name someString
into @Name someString -- convert from string to name
into @String someName -- convert from name to string

This type class does not have any laws, but it does have some expectations:

  • Conversions should be total. A conversion should never fail or crash. Avoid writing instances like Cast Int (Maybe Char). (It might be worthwhile to have a separate TryCast type class for this.)
  • Conversions should be unambiguous. For example there are many ways to decode a ByteString into Text, so you shouldn't provide an instance for that.
  • Conversions should be cheap, ideally free. For example converting from String to Text is probably fine, but converting from a UTF-8 encoded ByteString to Text is problematic.
  • Conversions should be lossless. In other words if you have Cast a b then no two a values should be converted to the same b value. For example Cast Int Integer is fine because every Int can be mapped to a corresponding Integer, but Cast Integer Int is not good because some Integers are out of bounds and would need to be clamped.
  • If you have both Cast a b and Cast b a, then cast . cast 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 it's up to you if you want to provide Cast a c. Sometimes using via is ergonomic enough, other times you want the extra instance. (It would be nice if we could provide instance (Cast a b, Cast b c) => Cast a c where cast = via @b.)

Minimal complete definition

Nothing

Methods

cast :: source -> target Source #

This method implements the conversion of a value between types. In practice most instances don't need an explicit implementation. At call sites you'll usually want to use from or into instead of cast.

The default implementation of cast simply calls coerce, which works for types that have the same runtime representation.

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

Instances

Instances details
Cast Bool Int Source #

fromEnum

Instance details

Defined in Witch

Methods

cast :: Bool -> Int Source #

Cast Char Int Source #

fromEnum

Instance details

Defined in Witch

Methods

cast :: Char -> Int Source #

Cast Float Double Source #

realToFrac

Instance details

Defined in Witch

Methods

cast :: Float -> Double Source #

Cast Int Integer Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Int -> Integer Source #

Cast Int8 Int16 Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Int8 -> Int16 Source #

Cast Int16 Int32 Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Int16 -> Int32 Source #

Cast Int32 Int64 Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Int32 -> Int64 Source #

Cast Integer Rational Source #

fromIntegral

Instance details

Defined in Witch

Cast Natural Integer Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Natural -> Integer Source #

Cast Word Natural Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Word -> Natural Source #

Cast Word8 Word16 Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Word8 -> Word16 Source #

Cast Word16 Word32 Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Word16 -> Word32 Source #

Cast Word32 Word64 Source #

fromIntegral

Instance details

Defined in Witch

Methods

cast :: Word32 -> Word64 Source #

Cast a a Source #

id

Instance details

Defined in Witch

Methods

cast :: a -> a Source #

Cast Void x Source #

absurd

Instance details

Defined in Witch

Methods

cast :: Void -> x Source #

Cast String Text Source #

pack

Note that some Char values cannot be represented in Text and will be replaced by U+FFFD.

Instance details

Defined in Witch

Methods

cast :: String -> Text Source #

Cast ByteString ByteString Source #

toStrict

Instance details

Defined in Witch

Cast ByteString ByteString Source #

fromStrict

Instance details

Defined in Witch

Cast Text Text Source #

toStrict

Instance details

Defined in Witch

Methods

cast :: Text0 -> Text Source #

Cast Text String Source #

unpack

Instance details

Defined in Witch

Methods

cast :: Text -> String Source #

Cast Text Text Source #

fromStrict

Instance details

Defined in Witch

Methods

cast :: Text -> Text0 Source #

Cast a (Maybe a) Source #

Just

Instance details

Defined in Witch

Methods

cast :: a -> Maybe a Source #

Cast a [a] Source #

pure

Instance details

Defined in Witch

Methods

cast :: a -> [a] Source #

Cast ByteString [Word8] Source #

unpack

Instance details

Defined in Witch

Methods

cast :: ByteString -> [Word8] Source #

Cast a (Either x a) Source #

Right

Instance details

Defined in Witch

Methods

cast :: a -> Either x a Source #

Cast a (Either a x) Source #

Left

Instance details

Defined in Witch

Methods

cast :: a -> Either a x Source #

Cast a (x -> a) Source #

const

Instance details

Defined in Witch

Methods

cast :: a -> x -> a Source #

Cast [Word8] ByteString Source #

pack

Instance details

Defined in Witch

Methods

cast :: [Word8] -> ByteString Source #

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

fromList

Note that this will remove duplicate elements from the list.

Instance details

Defined in Witch

Methods

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

Cast [a] (Seq a) Source #

fromList

Instance details

Defined in Witch

Methods

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

Cast (NonEmpty a) [a] Source #

toList

Instance details

Defined in Witch

Methods

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

Cast (Seq a) [a] Source #

toList

Instance details

Defined in Witch

Methods

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

Cast (Set a) [a] Source #

toAscList

Instance details

Defined in Witch

Methods

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

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

fromList

Note that if there are duplicate keys in the list, the one closest to the end will win.

Instance details

Defined in Witch

Methods

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

Cast (x, a) a Source #

snd

Instance details

Defined in Witch

Methods

cast :: (x, a) -> a Source #

Cast (a, x) a Source #

fst

Instance details

Defined in Witch

Methods

cast :: (a, x) -> a Source #

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

toAscList

Instance details

Defined in Witch

Methods

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

Cast (a, b) (b, a) Source #

swap

Instance details

Defined in Witch

Methods

cast :: (a, b) -> (b, a) Source #

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

This function converts a value from one type into another. This is intended to be used with the TypeApplications language extension. The Ambiguous type in the signature makes a type application required. If you'd prefer not to provide a type application, use cast instead.

As an example, here are a few ways to convert from an Int into an Integer:

from @Int @Integer 123
from @_ @Integer (123 :: Int)
from @Int @_ 123 :: Integer
from @Int 123 :: Integer

Often the context around an expression will make the explicit type signatures unnecessary. If you find yourself using a partial type signature, consider using into instead. For example:

let someInt = 123 :: Int
from @_ @Integer someInt -- avoid this
into @Integer someInt -- prefer this

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

This function converts a value from one type into another. This is the same as from except that the type variables are in the opposite order.

via :: forall through source target. (Cast source through, Cast through target) => source -> target Source #

This function converts a value from one type into another by going through some third type. This is the same as calling cast (or from or into) twice, but can sometimes be more convenient.

Note that the type in the middle of the conversion is the first type variable of this function. In other words, via @b @a @c first converts from a to b, and then from b to c. Often both a and c will be inferred from context, which means you can just write via @b.