to-1.2.0: Simple, safe, boring type conversions

Safe HaskellNone
LanguageHaskell2010

To

Contents

Description

Conversions to various things.

See the table of contents for the full list of types you can convert into.

Synopsis

Sequences

Vector

class ToVector a e where Source #

Methods

toVector :: a -> Vector e Source #

Turn into a Vector.

Instances
ToVector [a] a Source #
[a] -> Vector a
Instance details

Defined in To

Methods

toVector :: [a] -> Vector a Source #

ToVector (NonEmpty a) a Source #
NonEmpty a -> Vector a
Instance details

Defined in To

Methods

toVector :: NonEmpty a -> Vector a Source #

Unbox a => ToVector (Vector a) a Source #
unboxed Vector a -> Vector a
Instance details

Defined in To

Methods

toVector :: Vector a -> Vector0 a Source #

Storable a => ToVector (Vector a) a Source #
storable Vector a -> Vector a
Instance details

Defined in To

Methods

toVector :: Vector a -> Vector0 a Source #

Unboxed Vector

class ToUnboxedVector a e where Source #

Methods

toUnboxedVector :: a -> Vector e Source #

Turn into an unboxed Vector.

Instances
Unbox a => ToUnboxedVector [a] a Source #
[a] -> unboxed Vector a
Instance details

Defined in To

Methods

toUnboxedVector :: [a] -> Vector a Source #

Unbox a => ToUnboxedVector (NonEmpty a) a Source #
NonEmpty a -> unboxed Vector a
Instance details

Defined in To

(Unbox a, Storable a) => ToUnboxedVector (Vector a) a Source #
storable Vector a -> unboxed Vector a
Instance details

Defined in To

Unbox a => ToUnboxedVector (Vector a) a Source #
Vector a -> unboxed Vector a
Instance details

Defined in To

Storable Vector

class ToStorableVector a e where Source #

Methods

toStorableVector :: a -> Vector e Source #

Turn into a storable Vector.

Instances
Storable a => ToStorableVector [a] a Source #
[a] -> storable Vector a
Instance details

Defined in To

Methods

toStorableVector :: [a] -> Vector a Source #

Storable a => ToStorableVector (NonEmpty a) a Source #
NonEmpty a -> storable Vector a
Instance details

Defined in To

(Unbox a, Storable a) => ToStorableVector (Vector a) a Source #
unboxed Vector a -> storable Vector a
Instance details

Defined in To

Storable a => ToStorableVector (Vector a) a Source #
Vector a -> storable Vector a
Instance details

Defined in To

Maps

Map

class ToMap a k v | a -> k v, a k -> v, a v -> k where Source #

Methods

toMap :: a -> Map k v Source #

Turn into a Map.

Instances
(kv ~ (k, v), Ord k) => ToMap [kv] k v Source #
[(k, v)] -> Map k v
Instance details

Defined in To

Methods

toMap :: [kv] -> Map k v Source #

(kv ~ (k, v), Ord k) => ToMap (NonEmpty kv) k v Source #
NonEmpty (k, v) -> Map k v
Instance details

Defined in To

Methods

toMap :: NonEmpty kv -> Map k v Source #

ToMap (IntMap v) Int v Source #
IntMap v -> Map Int v
Instance details

Defined in To

Methods

toMap :: IntMap v -> Map Int v Source #

Ord k => ToMap (HashMap k v) k v Source #
HashMap k v -> Map k v
Instance details

Defined in To

Methods

toMap :: HashMap k v -> Map k v Source #

HashMap

class ToHashMap a k v | a -> k v, a k -> v, a v -> k where Source #

Methods

toHashMap :: a -> HashMap k v Source #

Turn into a HashMap.

Instances
(kv ~ (k, v), Eq k, Hashable k) => ToHashMap [kv] k v Source #
[(k, v)] -> HashMap k v
Instance details

Defined in To

Methods

toHashMap :: [kv] -> HashMap k v Source #

(kv ~ (k, v), Eq k, Hashable k) => ToHashMap (NonEmpty kv) k v Source #
NonEmpty (k, v) -> HashMap k v
Instance details

Defined in To

Methods

toHashMap :: NonEmpty kv -> HashMap k v Source #

ToHashMap (IntMap v) Int v Source #
IntMap v -> HashMap Int v
Instance details

Defined in To

Methods

toHashMap :: IntMap v -> HashMap Int v Source #

(Eq k, Hashable k) => ToHashMap (Map k v) k v Source #
Map k v -> HashMap k v
Instance details

Defined in To

Methods

toHashMap :: Map k v -> HashMap k v Source #

IntMap

class ToIntMap a v | a -> v where Source #

Methods

toIntMap :: a -> IntMap v Source #

Turn into an IntMap.

Instances
kv ~ (Int, v) => ToIntMap [kv] v Source #
[(Int, v)] -> IntMap v
Instance details

Defined in To

Methods

toIntMap :: [kv] -> IntMap v Source #

kv ~ (Int, v) => ToIntMap (NonEmpty kv) v Source #
NonEmpty (Int, v) -> IntMap v
Instance details

Defined in To

Methods

toIntMap :: NonEmpty kv -> IntMap v Source #

ToIntMap (Map Int v) v Source #
Map Int v -> IntMap v
Instance details

Defined in To

Methods

toIntMap :: Map Int v -> IntMap v Source #

ToIntMap (HashMap Int v) v Source #
HashMap Int v -> IntMap v
Instance details

Defined in To

Methods

toIntMap :: HashMap Int v -> IntMap v Source #

Sets

Set

class ToSet a k | a -> k where Source #

Methods

toSet :: a -> Set k Source #

Turn into a Set.

Instances
ToSet IntSet Int Source #
IntSet -> Set Int
Instance details

Defined in To

Methods

toSet :: IntSet -> Set Int Source #

Ord k => ToSet [k] k Source #
[k] -> Set k
Instance details

Defined in To

Methods

toSet :: [k] -> Set k Source #

Ord k => ToSet (NonEmpty k) k Source #
NonEmpty k -> Set k
Instance details

Defined in To

Methods

toSet :: NonEmpty k -> Set k Source #

Ord k => ToSet (HashSet k) k Source #
HashSet k -> Set k
Instance details

Defined in To

Methods

toSet :: HashSet k -> Set k Source #

HashSet

class ToHashSet a k | a -> k where Source #

Methods

toHashSet :: a -> HashSet k Source #

Turn into a HashSet.

Instances
ToHashSet IntSet Int Source #
IntSet -> HashSet Int
Instance details

Defined in To

(Eq k, Hashable k) => ToHashSet (NonEmpty k) k Source #
NonEmpty k -> HashSet k
Instance details

Defined in To

Methods

toHashSet :: NonEmpty k -> HashSet k Source #

(Eq k, Hashable k) => ToHashSet (Set k) k Source #
Set k -> HashSet k
Instance details

Defined in To

Methods

toHashSet :: Set k -> HashSet k Source #

IntSet

class ToIntSet a where Source #

Methods

toIntSet :: a -> IntSet Source #

Turn into an IntSet.

Instances
k ~ Int => ToIntSet [k] Source #
[Int] -> IntSet
Instance details

Defined in To

Methods

toIntSet :: [k] -> IntSet Source #

k ~ Int => ToIntSet (NonEmpty k) Source #
NonEmpty Int -> IntSet
Instance details

Defined in To

ToIntSet (Set Int) Source #
Set Int -> IntSet
Instance details

Defined in To

Methods

toIntSet :: Set Int -> IntSet Source #

ToIntSet (HashSet Int) Source #
HashSet Int -> IntSet
Instance details

Defined in To

Strings and bytestrings

String

class ToString a where Source #

Methods

toString :: a -> String Source #

Turn into String.

Instances
(TypeError (SpecifyDecoding ByteString "utf8ToString") :: Constraint) => ToString ByteString Source #

Use utf8ToString

Instance details

Defined in To

(TypeError (SpecifyDecoding ByteString "utf8ToString") :: Constraint) => ToString ByteString Source #

Use utf8ToString

Instance details

Defined in To

ToString Builder Source # 
Instance details

Defined in To

ToString Text Source # 
Instance details

Defined in To

Methods

toString :: Text -> String Source #

ToString Text Source # 
Instance details

Defined in To

Methods

toString :: Text -> String Source #

class Utf8ToString a where Source #

Methods

utf8ToString :: a -> String Source #

Decode UTF8-encoded text into String.

Malformed characters are replaced by U+FFFD (the Unicode replacement character).

Instances
Utf8ToString ByteString Source # 
Instance details

Defined in To

Utf8ToString ByteString Source # 
Instance details

Defined in To

Strict Text

class ToText a where Source #

Methods

toText :: a -> Text Source #

Turn into strict Text.

Instances
(TypeError (SpecifyDecoding ByteString "utf8ToText") :: Constraint) => ToText ByteString Source #

Use utf8ToText

Instance details

Defined in To

(TypeError (SpecifyDecoding ByteString "utf8ToText") :: Constraint) => ToText ByteString Source #

Use utf8ToText

Instance details

Defined in To

ToText Builder Source # 
Instance details

Defined in To

Methods

toText :: Builder -> Text Source #

ToText Text Source # 
Instance details

Defined in To

Methods

toText :: Text -> Text0 Source #

a ~ Char => ToText [a] Source #
String -> Text
Instance details

Defined in To

Methods

toText :: [a] -> Text Source #

class Utf8ToText a where Source #

Methods

utf8ToText :: a -> Text Source #

Decode UTF8-encoded text into strict Text.

Malformed characters are replaced by U+FFFD (the Unicode replacement character).

Instances
Utf8ToText ByteString Source # 
Instance details

Defined in To

Utf8ToText ByteString Source # 
Instance details

Defined in To

Lazy Text

class ToLazyText a where Source #

Methods

toLazyText :: a -> Text Source #

Turn into lazy Text.

Instances
(TypeError (SpecifyDecoding ByteString "utf8ToLazyText") :: Constraint) => ToLazyText ByteString Source #

Use utf8ToLazyText

Instance details

Defined in To

(TypeError (SpecifyDecoding ByteString "utf8ToLazyText") :: Constraint) => ToLazyText ByteString Source #

Use utf8ToLazyText

Instance details

Defined in To

ToLazyText Builder Source # 
Instance details

Defined in To

ToLazyText Text Source # 
Instance details

Defined in To

a ~ Char => ToLazyText [a] Source #
String -> Text
Instance details

Defined in To

Methods

toLazyText :: [a] -> Text Source #

class Utf8ToLazyText a where Source #

Methods

utf8ToLazyText :: a -> Text Source #

Decode UTF8-encoded text into lazy Text.

Malformed characters are replaced by U+FFFD (the Unicode replacement character).

Instances
Utf8ToLazyText ByteString Source # 
Instance details

Defined in To

Utf8ToLazyText ByteString Source # 
Instance details

Defined in To

Text Builder

class ToTextBuilder a where Source #

Methods

toTextBuilder :: a -> Builder Source #

Turn into text Builder.

Instances
(TypeError (SpecifyDecoding ByteString "utf8ToTextBuilder") :: Constraint) => ToTextBuilder ByteString Source #

Use utf8ToTextBuilder

Instance details

Defined in To

(TypeError (SpecifyDecoding ByteString "utf8ToTextBuilder") :: Constraint) => ToTextBuilder ByteString Source #

Use utf8ToTextBuilder

Instance details

Defined in To

ToTextBuilder Text Source # 
Instance details

Defined in To

ToTextBuilder Text Source # 
Instance details

Defined in To

a ~ Char => ToTextBuilder [a] Source #
String -> Text
Instance details

Defined in To

Methods

toTextBuilder :: [a] -> Builder Source #

class Utf8ToTextBuilder a where Source #

Methods

utf8ToTextBuilder :: a -> Builder Source #

Decode UTF8-encoded text into text Builder.

Malformed characters are replaced by U+FFFD (the Unicode replacement character).

Instances
Utf8ToTextBuilder ByteString Source # 
Instance details

Defined in To

Utf8ToTextBuilder ByteString Source # 
Instance details

Defined in To

Strict ByteString

class ToByteString a where Source #

Methods

toByteString :: a -> ByteString Source #

Turn into strict ByteString.

Instances
ToByteString ByteString Source # 
Instance details

Defined in To

(TypeError (SpecifyEncoding Builder "toUtf8ByteString") :: Constraint) => ToByteString Builder Source #

Use toUtf8ByteString

Instance details

Defined in To

(TypeError (SpecifyEncoding Text "toUtf8ByteString") :: Constraint) => ToByteString Text Source #

Use toUtf8ByteString

Instance details

Defined in To

(TypeError (SpecifyEncoding Text "toUtf8ByteString") :: Constraint) => ToByteString Text Source #

Use toUtf8ByteString

Instance details

Defined in To

(a ~ Char, (TypeError (SpecifyEncoding String "toUtf8ByteString") :: Constraint)) => ToByteString [a] Source #

Use toUtf8ByteString

Instance details

Defined in To

Methods

toByteString :: [a] -> ByteString Source #

class ToUtf8ByteString a where Source #

Methods

toUtf8ByteString :: a -> ByteString Source #

UTF8-encode text into ByteString.

Instances
ToUtf8ByteString Builder Source # 
Instance details

Defined in To

ToUtf8ByteString Text Source # 
Instance details

Defined in To

ToUtf8ByteString Text Source # 
Instance details

Defined in To

a ~ Char => ToUtf8ByteString [a] Source #
String -> ByteString
Instance details

Defined in To

Lazy ByteString

class ToLazyByteString a where Source #

Methods

toLazyByteString :: a -> ByteString Source #

Turn into lazy ByteString.

Instances
ToLazyByteString ByteString Source # 
Instance details

Defined in To

(TypeError (SpecifyEncoding Builder "toUtf8LazyByteString") :: Constraint) => ToLazyByteString Builder Source #

Use toUtf8LazyByteString

Instance details

Defined in To

(TypeError (SpecifyEncoding Text "toUtf8LazyByteString") :: Constraint) => ToLazyByteString Text Source #

Use toUtf8LazyByteString

Instance details

Defined in To

(TypeError (SpecifyEncoding Text "toUtf8LazyByteString") :: Constraint) => ToLazyByteString Text Source #

Use toUtf8LazyByteString

Instance details

Defined in To

(a ~ Char, (TypeError (SpecifyEncoding String "toUtf8LazyByteString") :: Constraint)) => ToLazyByteString [a] Source #

Use toUtf8LazyByteString

Instance details

Defined in To

class ToUtf8LazyByteString a where Source #

Methods

toUtf8LazyByteString :: a -> ByteString Source #

UTF8-encode text into lazy ByteString.

Instances
ToUtf8LazyByteString Builder Source # 
Instance details

Defined in To

ToUtf8LazyByteString Text Source # 
Instance details

Defined in To

ToUtf8LazyByteString Text Source # 
Instance details

Defined in To

a ~ Char => ToUtf8LazyByteString [a] Source #
String -> ByteString
Instance details

Defined in To