unbeliever-0.9.3.2: Opinionated Haskell Interoperability

Safe HaskellNone
LanguageHaskell2010

Core.Text.Bytes

Description

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.

Synopsis

Documentation

data Bytes Source #

A block of data in binary form.

Instances
Eq Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Methods

(==) :: Bytes -> Bytes -> Bool #

(/=) :: Bytes -> Bytes -> Bool #

Ord Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

(>=) :: Bytes -> Bytes -> Bool #

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Show Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Generic Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Hashable Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Methods

hashWithSalt :: Int -> Bytes -> Int #

hash :: Bytes -> Int #

Render Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Associated Types

type Token Bytes :: Type Source #

Binary Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Key Bytes Source # 
Instance details

Defined in Core.Data.Structures

type Rep Bytes Source # 
Instance details

Defined in Core.Text.Bytes

type Rep Bytes = D1 (MetaData "Bytes" "Core.Text.Bytes" "unbeliever-0.9.3.2-Jtx66YjcEMrHhyvsSL5WQ4" False) (C1 (MetaCons "StrictBytes" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString)))
type Token Bytes Source # 
Instance details

Defined in Core.Text.Bytes

type Token Bytes = ()

class Binary α where Source #

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.

Methods

fromBytes :: Bytes -> α Source #

intoBytes :: α -> Bytes Source #

Instances
Binary ByteString Source #

from Data.ByteString Strict

Instance details

Defined in Core.Text.Bytes

Binary ByteString Source #

from Data.ByteString.Lazy

Instance details

Defined in Core.Text.Bytes

Binary Rope Source # 
Instance details

Defined in Core.Text.Bytes

Binary Bytes Source # 
Instance details

Defined in Core.Text.Bytes

Binary [Word8] Source #

from Data.Word

Instance details

Defined in Core.Text.Bytes

hOutput :: Handle -> Bytes -> IO () Source #

Output the content of the Bytes to the specified Handle.

    hOutput h b

output 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.

hInput :: Handle -> IO Bytes Source #

Read the (entire) contents of a handle into a Bytes object.

If you want to read the entire contents of a file, you can do:

    contents <- withFile name ReadMode hInput

At any kind of scale, Streaming I/O is almost always for better, but for small files you need to pick apart this is fine.