Safe Haskell | None |
---|---|
Language | Haskell2010 |
Conversions to various things.
See the table of contents for the full list of types you can convert into.
Synopsis
- class ToVector a e where
- class ToUnboxedVector a e where
- toUnboxedVector :: a -> Vector e
- class ToStorableVector a e where
- toStorableVector :: a -> Vector e
- class ToMap a k v | a -> k v, a k -> v, a v -> k where
- class ToHashMap a k v | a -> k v, a k -> v, a v -> k where
- class ToIntMap a v | a -> v where
- class ToSet a k | a -> k where
- class ToHashSet a k | a -> k where
- class ToIntSet a where
- class ToString a where
- class Utf8ToString a where
- utf8ToString :: a -> String
- class ToText a where
- class Utf8ToText a where
- utf8ToText :: a -> Text
- class ToLazyText a where
- toLazyText :: a -> Text
- class Utf8ToLazyText a where
- utf8ToLazyText :: a -> Text
- class ToTextBuilder a where
- toTextBuilder :: a -> Builder
- class Utf8ToTextBuilder a where
- utf8ToTextBuilder :: a -> Builder
- class ToByteString a where
- toByteString :: a -> ByteString
- class ToUtf8ByteString a where
- toUtf8ByteString :: a -> ByteString
- class ToLazyByteString a where
- toLazyByteString :: a -> ByteString
- class ToUtf8LazyByteString a where
- toUtf8LazyByteString :: a -> ByteString
Sequences
Vector
Unboxed Vector
class ToUnboxedVector a e where Source #
toUnboxedVector :: a -> Vector e Source #
Turn into an unboxed Vector
.
Instances
Unbox a => ToUnboxedVector [a] a Source # | [a] -> unboxed Vector a |
Defined in To toUnboxedVector :: [a] -> Vector a Source # | |
Unbox a => ToUnboxedVector (NonEmpty a) a Source # | NonEmpty a -> unboxed Vector a |
(Unbox a, Storable a) => ToUnboxedVector (Vector a) a Source # | storable Vector a -> unboxed Vector a |
Unbox a => ToUnboxedVector (Vector a) a Source # | Vector a -> unboxed Vector a |
Storable Vector
class ToStorableVector a e where Source #
toStorableVector :: a -> Vector e Source #
Turn into a storable Vector
.
Instances
Storable a => ToStorableVector [a] a Source # | [a] -> storable Vector a |
Defined in To toStorableVector :: [a] -> Vector a Source # | |
Storable a => ToStorableVector (NonEmpty a) a Source # | NonEmpty a -> storable Vector a |
(Unbox a, Storable a) => ToStorableVector (Vector a) a Source # | unboxed Vector a -> storable Vector a |
Storable a => ToStorableVector (Vector a) a Source # | Vector a -> storable Vector a |
Maps
Map
class ToMap a k v | a -> k v, a k -> v, a v -> k where Source #
HashMap
class ToHashMap a k v | a -> k v, a k -> v, a v -> k where Source #
Instances
(kv ~ (k, v), Eq k, Hashable k) => ToHashMap [kv] k v Source # | [(k, v)] -> HashMap k v |
(kv ~ (k, v), Eq k, Hashable k) => ToHashMap (NonEmpty kv) k v Source # | NonEmpty (k, v) -> HashMap k v |
ToHashMap (IntMap v) Int v Source # | IntMap v -> HashMap Int v |
(Eq k, Hashable k) => ToHashMap (Map k v) k v Source # | Map k v -> HashMap k v |
IntMap
Sets
Set
HashSet
IntSet
Strings and bytestrings
String
class ToString a where Source #
Instances
(TypeError (SpecifyDecoding ByteString "utf8ToString") :: Constraint) => ToString ByteString Source # | Use |
(TypeError (SpecifyDecoding ByteString "utf8ToString") :: Constraint) => ToString ByteString Source # | Use |
ToString Builder Source # | |
ToString Text Source # | |
ToString Text Source # | |
class Utf8ToString a where Source #
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 # | |
Defined in To utf8ToString :: ByteString -> String Source # | |
Utf8ToString ByteString Source # | |
Defined in To utf8ToString :: ByteString -> String Source # |
Strict Text
Instances
(TypeError (SpecifyDecoding ByteString "utf8ToText") :: Constraint) => ToText ByteString Source # | Use |
(TypeError (SpecifyDecoding ByteString "utf8ToText") :: Constraint) => ToText ByteString Source # | Use |
ToText Builder Source # | |
ToText Text Source # | |
a ~ Char => ToText [a] Source # | String -> Text |
class Utf8ToText a where Source #
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 # | |
Defined in To utf8ToText :: ByteString -> Text Source # | |
Utf8ToText ByteString Source # | |
Defined in To utf8ToText :: ByteString -> Text Source # |
Lazy Text
class ToLazyText a where Source #
toLazyText :: a -> Text Source #
Turn into lazy Text
.
Instances
(TypeError (SpecifyDecoding ByteString "utf8ToLazyText") :: Constraint) => ToLazyText ByteString Source # | Use |
Defined in To toLazyText :: ByteString -> Text Source # | |
(TypeError (SpecifyDecoding ByteString "utf8ToLazyText") :: Constraint) => ToLazyText ByteString Source # | Use |
Defined in To toLazyText :: ByteString -> Text Source # | |
ToLazyText Builder Source # | |
ToLazyText Text Source # | |
a ~ Char => ToLazyText [a] Source # | String -> Text |
Defined in To toLazyText :: [a] -> Text Source # |
class Utf8ToLazyText a where Source #
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 # | |
Defined in To utf8ToLazyText :: ByteString -> Text Source # | |
Utf8ToLazyText ByteString Source # | |
Defined in To utf8ToLazyText :: ByteString -> Text Source # |
Text Builder
class ToTextBuilder a where Source #
toTextBuilder :: a -> Builder Source #
Turn into text Builder
.
Instances
(TypeError (SpecifyDecoding ByteString "utf8ToTextBuilder") :: Constraint) => ToTextBuilder ByteString Source # | |
Defined in To toTextBuilder :: ByteString -> Builder Source # | |
(TypeError (SpecifyDecoding ByteString "utf8ToTextBuilder") :: Constraint) => ToTextBuilder ByteString Source # | |
Defined in To toTextBuilder :: ByteString -> Builder Source # | |
ToTextBuilder Text Source # | |
ToTextBuilder Text Source # | |
a ~ Char => ToTextBuilder [a] Source # | String -> Text |
Defined in To toTextBuilder :: [a] -> Builder Source # |
class Utf8ToTextBuilder a where Source #
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 # | |
Defined in To | |
Utf8ToTextBuilder ByteString Source # | |
Defined in To |
Strict ByteString
class ToByteString a where Source #
toByteString :: a -> ByteString Source #
Turn into strict ByteString
.
Instances
ToByteString ByteString Source # | |
Defined in To toByteString :: ByteString -> ByteString0 Source # | |
(TypeError (SpecifyEncoding Builder "toUtf8ByteString") :: Constraint) => ToByteString Builder Source # | Use |
Defined in To toByteString :: Builder -> ByteString Source # | |
(TypeError (SpecifyEncoding Text "toUtf8ByteString") :: Constraint) => ToByteString Text Source # | Use |
Defined in To toByteString :: Text -> ByteString Source # | |
(TypeError (SpecifyEncoding Text "toUtf8ByteString") :: Constraint) => ToByteString Text Source # | Use |
Defined in To toByteString :: Text -> ByteString Source # | |
(a ~ Char, (TypeError (SpecifyEncoding String "toUtf8ByteString") :: Constraint)) => ToByteString [a] Source # | Use |
Defined in To toByteString :: [a] -> ByteString Source # |
class ToUtf8ByteString a where Source #
toUtf8ByteString :: a -> ByteString Source #
UTF8-encode text into ByteString
.
Instances
ToUtf8ByteString Builder Source # | |
Defined in To toUtf8ByteString :: Builder -> ByteString Source # | |
ToUtf8ByteString Text Source # | |
Defined in To toUtf8ByteString :: Text -> ByteString Source # | |
ToUtf8ByteString Text Source # | |
Defined in To toUtf8ByteString :: Text -> ByteString Source # | |
a ~ Char => ToUtf8ByteString [a] Source # | String -> ByteString |
Defined in To toUtf8ByteString :: [a] -> ByteString Source # |
Lazy ByteString
class ToLazyByteString a where Source #
toLazyByteString :: a -> ByteString Source #
Turn into lazy ByteString
.
Instances
ToLazyByteString ByteString Source # | |
Defined in To | |
(TypeError (SpecifyEncoding Builder "toUtf8LazyByteString") :: Constraint) => ToLazyByteString Builder Source # | |
Defined in To toLazyByteString :: Builder -> ByteString Source # | |
(TypeError (SpecifyEncoding Text "toUtf8LazyByteString") :: Constraint) => ToLazyByteString Text Source # | |
Defined in To toLazyByteString :: Text -> ByteString Source # | |
(TypeError (SpecifyEncoding Text "toUtf8LazyByteString") :: Constraint) => ToLazyByteString Text Source # | |
Defined in To toLazyByteString :: Text -> ByteString Source # | |
(a ~ Char, (TypeError (SpecifyEncoding String "toUtf8LazyByteString") :: Constraint)) => ToLazyByteString [a] Source # | |
Defined in To toLazyByteString :: [a] -> ByteString Source # |
class ToUtf8LazyByteString a where Source #
toUtf8LazyByteString :: a -> ByteString Source #
UTF8-encode text into lazy ByteString
.
Instances
ToUtf8LazyByteString Builder Source # | |
Defined in To | |
ToUtf8LazyByteString Text Source # | |
Defined in To | |
ToUtf8LazyByteString Text Source # | |
Defined in To | |
a ~ Char => ToUtf8LazyByteString [a] Source # | String -> ByteString |
Defined in To toUtf8LazyByteString :: [a] -> ByteString Source # |