Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module enables debugging all ByteString
to Text
to String
conversions.
This is an internal module.
Since: 0.5.67
Synopsis
- data Text
- type LazyText = Text
- data ByteString
- type LazyByteString = ByteString
- class Textual a where
- renderToText :: HasCallStack => a -> Either String Text
- parseFromText :: HasCallStack => Text -> Either String a
- writeTextFile :: (HasCallStack, MonadIO m) => FilePath -> Text -> m ()
- unsafeRenderToText :: (Textual a, HasCallStack) => a -> Text
- unsafeParseFromText :: (Textual a, HasCallStack) => Text -> a
- parseFromTextWithErrorMessage :: (HasCallStack, Textual a) => String -> Text -> Either String a
- encodeAsUtf8LazyByteString :: HasCallStack => String -> LazyByteString
Documentation
A space efficient, packed, unboxed Unicode text type.
Instances
Lazy texts.
A type alias to Text
that can be used everywhere such that
references don't need to be qualified with the complete module name everywere.
Since: 0.5.67
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
type LazyByteString = ByteString Source #
Lazy byte strings.
A type alias to ByteString
that can be used everywhere such that
references don't need to be qualified with the complete module name everywere.
Since: 0.5.67
class Textual a where Source #
A class for values that can be converted to/from Text
.
Since: 0.5.67
renderToText :: HasCallStack => a -> Either String Text Source #
parseFromText :: HasCallStack => Text -> Either String a Source #
Instances
Textual String Source # | |
Textual ByteString Source # | Convert a Since: 0.5.67 |
Defined in B9.Text renderToText :: ByteString -> Either String Text Source # parseFromText :: Text -> Either String ByteString Source # | |
Textual Text Source # | |
Textual LazyByteString Source # | Convert a Since: 0.5.67 |
Defined in B9.Text | |
Textual YamlObject Source # | |
Defined in B9.Artifact.Content.YamlObject renderToText :: YamlObject -> Either String Text Source # parseFromText :: Text -> Either String YamlObject Source # | |
Textual ErlangPropList Source # | |
Defined in B9.Artifact.Content.ErlangPropList | |
Textual CloudConfigYaml Source # | |
Defined in B9.Artifact.Content.CloudConfigYaml |
writeTextFile :: (HasCallStack, MonadIO m) => FilePath -> Text -> m () Source #
Render a Text
to a file.
Since: 0.5.67
unsafeRenderToText :: (Textual a, HasCallStack) => a -> Text Source #
Render a Text
via renderToText
and throw a runtime exception when rendering fails.
Since: 0.5.67
unsafeParseFromText :: (Textual a, HasCallStack) => Text -> a Source #
Parse a Text
via parseFromText
and throw a runtime exception when parsing fails.
Since: 0.5.67
parseFromTextWithErrorMessage Source #
:: (HasCallStack, Textual a) | |
=> String | An arbitrary string for error messages |
-> Text | |
-> Either String a |
Parse the given Text
. -- Return Left errorMessage
or Right a
.
encodeAsUtf8LazyByteString :: HasCallStack => String -> LazyByteString Source #
Encode a String
as UTF-8 encoded into a LazyByteString
.
Since: 0.5.67