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

Witch

Description

This module provides the From 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

Documentation

class From a b where Source #

This type class represents a way to convert values from some type into another type. The constraint From 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 From String Name
instance From 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 From Int (Maybe Char). (It might be worthwhile to have a separate TryFrom 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 From a b then no two a values should be converted to the same b value. For example From Int Integer is fine because every Int can be mapped to a corresponding Integer, but From Integer Int is not good because some Integers are out of bounds and would need to be clamped.
  • If you have both From a b and From b a, then from . from should be the same as id. In other words a and b are isomorphic.
  • If you have both From a b and From b c, then it's up to you if you want to provide From a c. Sometimes using via is ergonomic enough, other times you want the extra instance. (It would be nice if we could provide instance (From a b, From b c) => From a c where from = via @b.)

Minimal complete definition

Nothing

Methods

from :: a -> b Source #

This method converts a value from one type into another. This is intended to be used with the TypeApplications language extension. For 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
from (123 :: Int) :: 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

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

default from :: Coercible a b => a -> b Source #

Instances

Instances details
From Bool Int Source #

fromEnum

Instance details

Defined in Witch

Methods

from :: Bool -> Int Source #

From Char Int Source #

fromEnum

Instance details

Defined in Witch

Methods

from :: Char -> Int Source #

From Float Double Source #

realToFrac

Instance details

Defined in Witch

Methods

from :: Float -> Double Source #

From Int Integer Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Int -> Integer Source #

From Int8 Int16 Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Int8 -> Int16 Source #

From Int16 Int32 Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Int16 -> Int32 Source #

From Int32 Int64 Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Int32 -> Int64 Source #

From Integer Rational Source #

fromIntegral

Instance details

Defined in Witch

From Natural Integer Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Natural -> Integer Source #

From Word Natural Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Word -> Natural Source #

From Word8 Word16 Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Word8 -> Word16 Source #

From Word16 Word32 Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Word16 -> Word32 Source #

From Word32 Word64 Source #

fromIntegral

Instance details

Defined in Witch

Methods

from :: Word32 -> Word64 Source #

From a a Source #

id

Instance details

Defined in Witch

Methods

from :: a -> a Source #

From Void x Source #

absurd

Instance details

Defined in Witch

Methods

from :: Void -> x Source #

From String Text Source #

pack

Instance details

Defined in Witch

Methods

from :: String -> Text Source #

From ByteString ByteString Source #

toStrict

Instance details

Defined in Witch

From ByteString ByteString Source #

fromStrict

Instance details

Defined in Witch

From Text Text Source #

toStrict

Instance details

Defined in Witch

Methods

from :: Text0 -> Text Source #

From Text String Source #

unpack

Instance details

Defined in Witch

Methods

from :: Text -> String Source #

From Text Text Source #

fromStrict

Instance details

Defined in Witch

Methods

from :: Text -> Text0 Source #

From a (Maybe a) Source #

Just

Instance details

Defined in Witch

Methods

from :: a -> Maybe a Source #

From a [a] Source #

pure

Instance details

Defined in Witch

Methods

from :: a -> [a] Source #

From ByteString [Word8] Source #

unpack

Instance details

Defined in Witch

Methods

from :: ByteString -> [Word8] Source #

From a (Either x a) Source #

Right

Instance details

Defined in Witch

Methods

from :: a -> Either x a Source #

From a (Either a x) Source #

Left

Instance details

Defined in Witch

Methods

from :: a -> Either a x Source #

From a (x -> a) Source #

const

Instance details

Defined in Witch

Methods

from :: a -> x -> a Source #

From [Word8] ByteString Source #

pack

Instance details

Defined in Witch

Methods

from :: [Word8] -> ByteString Source #

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

fromList

Note that this will remove duplicate elements from the list.

Instance details

Defined in Witch

Methods

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

From [a] (Seq a) Source #

fromList

Instance details

Defined in Witch

Methods

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

From (NonEmpty a) [a] Source #

toList

Instance details

Defined in Witch

Methods

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

From (Seq a) [a] Source #

toList

Instance details

Defined in Witch

Methods

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

From (Set a) [a] Source #

toAscList

Instance details

Defined in Witch

Methods

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

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

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

From (x, a) a Source #

snd

Instance details

Defined in Witch

Methods

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

From (a, x) a Source #

fst

Instance details

Defined in Witch

Methods

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

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

toAscList

Instance details

Defined in Witch

Methods

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

From (a, b) (b, a) Source #

swap

Instance details

Defined in Witch

Methods

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

into :: forall b a. From a b => a -> b 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 b a c. (From a b, From b c) => a -> c Source #

This function converts a value from one type into another by going through some third type. This is the same as calling 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.