Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Binary (as opposed to textual) data is encountered in weird corners of the
Haskell ecosystem. We tend to forget (for example) that the content recieved
from a web server is not text until we convert it from UTF-8 (if that's what
it is); and of course that glosses over the fact that something of
content-type image/jpeg
is not text in any way, shape, or form.
Bytes also show up when working with crypto algorithms, taking hashes, and when doing serialization to external binary formats. Although we frequently display these in terminals (and in URLs!) as text, but we take for granted that we have actually deserialized the data or rendered the it in hexidecimal or base64 or...
This module presents a simple wrapper around various representations of binary data to make it easier to interoperate with libraries supplying or consuming bytes.
Documentation
A block of data in binary form.
Instances
Generic Bytes Source # | |
Show Bytes Source # | |
Binary Bytes Source # | |
Textual Bytes Source # | |
Render Bytes Source # | |
Eq Bytes Source # | |
Ord Bytes Source # | |
Hashable Bytes Source # | |
Defined in Core.Text.Bytes | |
type Rep Bytes Source # | |
Defined in Core.Text.Bytes type Rep Bytes = D1 ('MetaData "Bytes" "Core.Text.Bytes" "core-text-0.3.8.1-KEEtRRMfJlNIUNmGCyYR34" 'True) (C1 ('MetaCons "StrictBytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
type Token Bytes Source # | |
Defined in Core.Text.Utilities |
emptyBytes :: Bytes Source #
A zero-length Bytes
.
packBytes :: String -> Bytes Source #
For the annoyingly common case of needing to take an ASCII string literal in
your code and use it as a bunch of Bytes
.
Done via Data.ByteString.Char8 so all Char
s will be truncated to 8 bits
(i.e. Latin-1 characters less than 255). You should probably consider this
to be unsafe. Also note that we deliberately do not have a [Char]
instance
of Binary
; if you need to come back to a textual representation use
intoRope
.
Conversion to and from various types containing binary data into our convenience Bytes type.
As often as not these conversions are expensive; these methods are here just to wrap calling the relevant functions in a uniform interface.
Instances
Binary Builder Source # | |
Binary ByteString Source # | from Data.ByteString Strict |
Defined in Core.Text.Bytes fromBytes :: Bytes -> ByteString Source # intoBytes :: ByteString -> Bytes Source # | |
Binary ByteString Source # | from Data.ByteString.Lazy |
Defined in Core.Text.Bytes fromBytes :: Bytes -> ByteString Source # intoBytes :: ByteString -> Bytes Source # | |
Binary Bytes Source # | |
Binary Rope Source # | |
Binary [Word8] Source # | from Data.Word |
hOutput :: Handle -> Bytes -> IO () Source #
Output the content of the Bytes
to the specified Handle
.
hOutput h b
outputEntire
provides a convenient way to write a Bytes
to
a file or socket handle from within the Program
monad.
Don't use this function to write to stdout
if you are using any of the other
output or logging facililities of this libarary as you will corrupt the
ordering of output on the user's terminal. Instead do:
write
(intoRope
b)
on the assumption that the bytes in question are UTF-8 (or plain ASCII) encoded.
Internals
unBytes :: Bytes -> ByteString Source #
Access the strict ByteString
underlying the Bytes
type.