buildable-0.1.0.2: Typeclass for builders of linear data structures

MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone

Data.Buildable

Contents

Description

Various linear data structures can be expensive to construct in a repetitive fashion. For example, to append a single value to the end of a list is O(n), and as such doing so repeatedly is recommended against.

As such, to efficiently construct such structures we have the notion of a builder. This can be used to more efficiently prepend and append values, and at the end we "run" the builder to construct the overall value.

This module provides an abstraction over various builders for specific data structures. It also aims to minimise the number of functions required to add various values to the builder by using a typeclass and newtype wrappers.

To construct a value from it's builder:

  1. Start with either mempty for an empty Builder, or if you have an initial value use fromValue.
  2. Add initial values to the front or back using prepend / <| or append / |> respectively.
  3. Once you've finished constructing your builder, create your final value with build.

Note: all instances are defined for both strict and lazy ByteString and Text values.

Synopsis

Typeclasses

class (BuildFrom (Builder a) a, BuildFrom (Builder a) (Unit a)) => Buildable a whereSource

A linear data structure a is buildable if we can prepend and append both values of the data structure in question and its constituent elements to the builder.

Associated Types

type Unit a Source

The individual elements.

type Builder a Source

Methods

build :: Builder a -> aSource

Build the actual data structure.

Instances

Buildable ByteString

Lazy ByteStrings. This instance should be preferred over the one for strict ByteStrings.

Buildable ByteString

Strict ByteStrings. This instance goes via lazy ByteStrings, and as such they should be preferred.

Buildable Text 
Buildable Text 
Buildable [a] 
Buildable (Seq a) 
Buildable b => Buildable (Chunked b) 

class Monoid b => BuildFrom b a whereSource

Which values can be built from other values?

Minimal complete definition:

  • fromValue

Methods

fromValue :: a -> bSource

Create a builder from an initial value.

prepend :: a -> b -> bSource

Add a value to the front.

append :: b -> a -> bSource

Add a value to the end.

Instances

BuildFrom Builder Char 
BuildFrom Builder String 
BuildFrom Builder Text 
BuildFrom Builder Text 
BuildFrom Builder Int8 
BuildFrom Builder Word8 
BuildFrom Builder ByteString 
BuildFrom Builder ByteString 
BuildFrom Builder (Utf32 (LittleEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the LittleEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (LittleEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the LittleEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (BigEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the BigEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (BigEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the BigEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf16 (LittleEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the LittleEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (LittleEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the LittleEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (BigEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the BigEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (BigEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the BigEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf8 ByteString)

For lazy ByteStrings; goes via a lazy Text.

BuildFrom Builder (Utf8 ByteString)

For strict ByteStrings; goes via a strict Text.

BuildFrom Builder (Char8 ByteString)

For lazy ByteStrings; goes via a lazy Text.

BuildFrom Builder (Char8 ByteString)

For strict ByteStrings; goes via a strict Text.

BuildFrom Builder (LittleEndian (Utf32 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf32 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf32 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf32 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf16 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf16 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf16 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf16 (LittleEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf32 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf32 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf32 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf32 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf16 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf16 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf16 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf16 (BigEndian ByteString) instance.

BuildFrom Builder (Utf32 (LittleEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the LittleEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (LittleEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the LittleEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (BigEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the BigEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (BigEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the BigEndian (Utf32 Text) instance.

BuildFrom Builder (Utf16 (LittleEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the LittleEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (LittleEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the LittleEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (BigEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the BigEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (BigEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the BigEndian (Utf16 Text) instance.

BuildFrom Builder (Utf8 Char) 
BuildFrom Builder (Utf8 String) 
BuildFrom Builder (Utf8 Text)

For lazy Text values; goes via a lazy ByteString.

BuildFrom Builder (Utf8 Text)

For strict Text values; goes via a strict ByteString.

BuildFrom Builder (Char8 Char) 
BuildFrom Builder (Char8 String) 
BuildFrom Builder (Char7 Char) 
BuildFrom Builder (Char7 String) 
BuildFrom Builder (HexFixed Double)

Uses 16 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Float)

Uses 8 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int8)

Uses 2 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int16)

Uses 4 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int32)

Uses 8 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int64)

Uses 16 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word8)

Uses 2 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word16)

Uses 4 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word32)

Uses 8 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word64)

Uses 16 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed ByteString) 
BuildFrom Builder (HexFixed ByteString) 
BuildFrom Builder (Hex Word) 
BuildFrom Builder (Hex Word8) 
BuildFrom Builder (Hex Word16) 
BuildFrom Builder (Hex Word32) 
BuildFrom Builder (Hex Word64) 
BuildFrom Builder (Dec Double)

Currently slow.

BuildFrom Builder (Dec Float)

Currently slow.

BuildFrom Builder (Dec Int) 
BuildFrom Builder (Dec Int8) 
BuildFrom Builder (Dec Int16) 
BuildFrom Builder (Dec Int32) 
BuildFrom Builder (Dec Int64) 
BuildFrom Builder (Dec Integer) 
BuildFrom Builder (Dec Word) 
BuildFrom Builder (Dec Word8) 
BuildFrom Builder (Dec Word16) 
BuildFrom Builder (Dec Word32) 
BuildFrom Builder (Dec Word64) 
BuildFrom Builder (LittleEndian Double) 
BuildFrom Builder (LittleEndian Float) 
BuildFrom Builder (LittleEndian Int16) 
BuildFrom Builder (LittleEndian Int32) 
BuildFrom Builder (LittleEndian Int64) 
BuildFrom Builder (LittleEndian Word16) 
BuildFrom Builder (LittleEndian Word32) 
BuildFrom Builder (LittleEndian Word64) 
BuildFrom Builder (LittleEndian (Utf32 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf32 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf32 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf32 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf16 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf16 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf16 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf16 (LittleEndian Text) instance.

BuildFrom Builder (BigEndian Double) 
BuildFrom Builder (BigEndian Float) 
BuildFrom Builder (BigEndian Int16) 
BuildFrom Builder (BigEndian Int32) 
BuildFrom Builder (BigEndian Int64) 
BuildFrom Builder (BigEndian Word16) 
BuildFrom Builder (BigEndian Word32) 
BuildFrom Builder (BigEndian Word64) 
BuildFrom Builder (BigEndian (Utf32 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf32 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf32 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf32 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf16 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf16 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf16 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf16 (BigEndian Text) instance.

BuildFrom [a] a 
BuildFrom (DList [a]) a 
BuildFrom (DList a) a 
BuildFrom (Seq a) a 
CanBuildFrom b a => BuildFrom (ChunkedBuilder b) a 
BuildFrom (DList a) [a] 
BuildFrom (Seq a) [a] 
BuildFrom (Seq a) (Seq a) 
Buildable b => BuildFrom (ChunkedBuilder b) (Chunked b) 

type CanBuildFrom b a = (Buildable b, BuildFrom (Builder b) a)Source

CanBuildFrom b a states that we can build a value of type b with values of type a.

singleton :: CanBuildFrom b a => a -> bSource

(<|) :: BuildFrom b a => a -> b -> bSource

An alias for prepend.

Mnemonic: the arrow points to the new value.

(|>) :: BuildFrom b a => b -> a -> bSource

An alias for append.

Mnemonic: the arrow points to the new value.

Chunked builder

For either testing purposes or some other reason, rather than actually creating an overall value you may actually want a list of a Buildable type.

The Chunked type allows you to efficiently create a list of such values by converting every provided value into the specified type.

newtype Chunked a Source

An explicit chunkified representation of a Builder. If we have a polymorphic expression buildValue that can be used to build something of type b, then the following are equivalent:

 'build' buildValue == mconcat . unChunk $ build buildValue

Constructors

Chunks 

Fields

unChunk :: [a]
 

Instances

Functor Chunked 
Eq a => Eq (Chunked a) 
Ord a => Ord (Chunked a) 
Read a => Read (Chunked a) 
Show a => Show (Chunked a) 
Monoid (Chunked a) 
Buildable b => Buildable (Chunked b) 
Buildable b => BuildFrom (ChunkedBuilder b) (Chunked b) 

newtype ChunkedBuilder a Source

You probably won't actually need to use this type; it's defined solely to be the Builder for Chunked.

Constructors

CB 

Fields

unCB :: DList a
 

ByteString Builders

There are various ways that numeric and textual types can be built into part of a ByteString (be it strict or lazy). To be able to choose between these, various wrapper types have been defined.

What you can add to the ByteString Builder:

  • Strict and lazy ByteStrings.
  • Numeric types, though most require a wrapper to disambiguate how to add it (see below)/
  • Char and String and both strict and lazy Text values after choosing an appropriate encoding (see below for wrapper types).

Numeric wrappers

Apart from Word8 and Int8, all numeric types need to be specified whether they should be encoded using BigEndian or LittleEndian format (with the exception of decimal representation using Dec).

All wrappers derive the various numeric type classes so that you can still perform various calculations on them.

newtype BigEndian a Source

Explicitly state that a number should be encoded in big-endian format.

Constructors

BE 

Fields

unBE :: a
 

Instances

BuildFrom Builder (Utf32 (BigEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the BigEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (BigEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the BigEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf16 (BigEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the BigEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (BigEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the BigEndian (Utf16 ByteString) instance.

BuildFrom Builder (BigEndian (Utf32 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf32 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf32 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf32 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf16 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf16 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf16 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf16 (BigEndian ByteString) instance.

BuildFrom Builder (Utf32 (BigEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the BigEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (BigEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the BigEndian (Utf32 Text) instance.

BuildFrom Builder (Utf16 (BigEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the BigEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (BigEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the BigEndian (Utf16 Text) instance.

BuildFrom Builder (BigEndian Double) 
BuildFrom Builder (BigEndian Float) 
BuildFrom Builder (BigEndian Int16) 
BuildFrom Builder (BigEndian Int32) 
BuildFrom Builder (BigEndian Int64) 
BuildFrom Builder (BigEndian Word16) 
BuildFrom Builder (BigEndian Word32) 
BuildFrom Builder (BigEndian Word64) 
BuildFrom Builder (BigEndian (Utf32 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf32 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf32 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf32 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf16 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf16 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf16 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf16 (BigEndian Text) instance.

Bounded a => Bounded (BigEndian a) 
Enum a => Enum (BigEndian a) 
Eq a => Eq (BigEndian a) 
Floating a => Floating (BigEndian a) 
Fractional a => Fractional (BigEndian a) 
Integral a => Integral (BigEndian a) 
Num a => Num (BigEndian a) 
Ord a => Ord (BigEndian a) 
Read a => Read (BigEndian a) 
Real a => Real (BigEndian a) 
RealFloat a => RealFloat (BigEndian a) 
RealFrac a => RealFrac (BigEndian a) 
Show a => Show (BigEndian a) 

newtype LittleEndian a Source

Explicitly state that a number should be encoded in little-endian format.

Constructors

LE 

Fields

unLE :: a
 

Instances

BuildFrom Builder (Utf32 (LittleEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the LittleEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (LittleEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the LittleEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf16 (LittleEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the LittleEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (LittleEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the LittleEndian (Utf16 ByteString) instance.

BuildFrom Builder (LittleEndian (Utf32 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf32 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf32 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf32 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf16 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf16 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf16 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf16 (LittleEndian ByteString) instance.

BuildFrom Builder (Utf32 (LittleEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the LittleEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (LittleEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the LittleEndian (Utf32 Text) instance.

BuildFrom Builder (Utf16 (LittleEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the LittleEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (LittleEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the LittleEndian (Utf16 Text) instance.

BuildFrom Builder (LittleEndian Double) 
BuildFrom Builder (LittleEndian Float) 
BuildFrom Builder (LittleEndian Int16) 
BuildFrom Builder (LittleEndian Int32) 
BuildFrom Builder (LittleEndian Int64) 
BuildFrom Builder (LittleEndian Word16) 
BuildFrom Builder (LittleEndian Word32) 
BuildFrom Builder (LittleEndian Word64) 
BuildFrom Builder (LittleEndian (Utf32 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf32 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf32 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf32 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf16 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf16 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf16 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf16 (LittleEndian Text) instance.

Bounded a => Bounded (LittleEndian a) 
Enum a => Enum (LittleEndian a) 
Eq a => Eq (LittleEndian a) 
Floating a => Floating (LittleEndian a) 
Fractional a => Fractional (LittleEndian a) 
Integral a => Integral (LittleEndian a) 
Num a => Num (LittleEndian a) 
Ord a => Ord (LittleEndian a) 
Read a => Read (LittleEndian a) 
Real a => Real (LittleEndian a) 
RealFloat a => RealFloat (LittleEndian a) 
RealFrac a => RealFrac (LittleEndian a) 
Show a => Show (LittleEndian a) 

newtype Dec a Source

Encode a number as its decimal representation with ASCII-encoded characters.

Constructors

Dec 

Fields

unDec :: a
 

Instances

BuildFrom Builder (Dec Double)

Currently slow.

BuildFrom Builder (Dec Float)

Currently slow.

BuildFrom Builder (Dec Int) 
BuildFrom Builder (Dec Int8) 
BuildFrom Builder (Dec Int16) 
BuildFrom Builder (Dec Int32) 
BuildFrom Builder (Dec Int64) 
BuildFrom Builder (Dec Integer) 
BuildFrom Builder (Dec Word) 
BuildFrom Builder (Dec Word8) 
BuildFrom Builder (Dec Word16) 
BuildFrom Builder (Dec Word32) 
BuildFrom Builder (Dec Word64) 
Bounded a => Bounded (Dec a) 
Enum a => Enum (Dec a) 
Eq a => Eq (Dec a) 
Floating a => Floating (Dec a) 
Fractional a => Fractional (Dec a) 
Integral a => Integral (Dec a) 
Num a => Num (Dec a) 
Ord a => Ord (Dec a) 
Read a => Read (Dec a) 
Real a => Real (Dec a) 
RealFloat a => RealFloat (Dec a) 
RealFrac a => RealFrac (Dec a) 
Show a => Show (Dec a) 

newtype Hex a Source

Encode a number as its hexadecimal representation with ASCII-encoded (lower-case) characters using the shortest possible representation. For fixed-width encoding use HexFixed instead.

Constructors

Hex 

Fields

unHex :: a
 

Instances

BuildFrom Builder (Hex Word) 
BuildFrom Builder (Hex Word8) 
BuildFrom Builder (Hex Word16) 
BuildFrom Builder (Hex Word32) 
BuildFrom Builder (Hex Word64) 
Bounded a => Bounded (Hex a) 
Enum a => Enum (Hex a) 
Eq a => Eq (Hex a) 
Floating a => Floating (Hex a) 
Fractional a => Fractional (Hex a) 
Integral a => Integral (Hex a) 
Num a => Num (Hex a) 
Ord a => Ord (Hex a) 
Read a => Read (Hex a) 
Real a => Real (Hex a) 
RealFloat a => RealFloat (Hex a) 
RealFrac a => RealFrac (Hex a) 
Show a => Show (Hex a) 

newtype HexFixed a Source

Encode a number as its hexadecimal representation with ASCII-encoded (lower-case) characters using a fixed number of hexadecimal digits. For shortest-width encoding use Hex instead.

Constructors

HexFixed 

Fields

unHexFixed :: a
 

Instances

BuildFrom Builder (HexFixed Double)

Uses 16 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Float)

Uses 8 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int8)

Uses 2 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int16)

Uses 4 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int32)

Uses 8 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Int64)

Uses 16 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word8)

Uses 2 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word16)

Uses 4 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word32)

Uses 8 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed Word64)

Uses 16 nibbles/hexadecimal digits.

BuildFrom Builder (HexFixed ByteString) 
BuildFrom Builder (HexFixed ByteString) 
Bounded a => Bounded (HexFixed a) 
Enum a => Enum (HexFixed a) 
Eq a => Eq (HexFixed a) 
Floating a => Floating (HexFixed a) 
Fractional a => Fractional (HexFixed a) 
Integral a => Integral (HexFixed a) 
Num a => Num (HexFixed a) 
Ord a => Ord (HexFixed a) 
Read a => Read (HexFixed a) 
Real a => Real (HexFixed a) 
RealFloat a => RealFloat (HexFixed a) 
RealFrac a => RealFrac (HexFixed a) 
Show a => Show (HexFixed a) 

Textual wrappers

There are various different encodings that can be used to encode textual data as a series of binary digits. As such, it is necessary to specify which encoding you want to use.

For Utf16 and Utf32 it is also necessary to specify whether you want to use a BigEndian or LittleEndian format; the order of newtype wrappers doesn't matter.

These are also used to encode a ByteString into the Builder for Text values (both strict and lazy).

newtype Char7 a Source

Unicode codepoints are truncated to 7 bits and prefixed with a leading 0. For the codepoints 0-127 this corresponds to the ASCII encoding.

Constructors

Char7 

Fields

unChar7 :: a
 

Instances

BuildFrom Builder (Char7 Char) 
BuildFrom Builder (Char7 String) 
Bounded a => Bounded (Char7 a) 
Enum a => Enum (Char7 a) 
Eq a => Eq (Char7 a) 
Ord a => Ord (Char7 a) 
Read a => Read (Char7 a) 
Show a => Show (Char7 a) 
IsString a => IsString (Char7 a) 

newtype Char8 a Source

Unicode codepoints are truncated to 8 bits. For the codepoints 0-255 this corresponds to the ISO/IEC 8859-1 (aka Latin-1) encoding.

Constructors

Char8 

Fields

unChar8 :: a
 

Instances

BuildFrom Builder (Char8 ByteString)

For lazy ByteStrings; goes via a lazy Text.

BuildFrom Builder (Char8 ByteString)

For strict ByteStrings; goes via a strict Text.

BuildFrom Builder (Char8 Char) 
BuildFrom Builder (Char8 String) 
Bounded a => Bounded (Char8 a) 
Enum a => Enum (Char8 a) 
Eq a => Eq (Char8 a) 
Ord a => Ord (Char8 a) 
Read a => Read (Char8 a) 
Show a => Show (Char8 a) 
IsString a => IsString (Char8 a) 

newtype Utf8 a Source

Encode a textual value using UTF-8.

Constructors

Utf8 

Fields

unUtf8 :: a
 

Instances

BuildFrom Builder (Utf8 ByteString)

For lazy ByteStrings; goes via a lazy Text.

BuildFrom Builder (Utf8 ByteString)

For strict ByteStrings; goes via a strict Text.

BuildFrom Builder (Utf8 Char) 
BuildFrom Builder (Utf8 String) 
BuildFrom Builder (Utf8 Text)

For lazy Text values; goes via a lazy ByteString.

BuildFrom Builder (Utf8 Text)

For strict Text values; goes via a strict ByteString.

Bounded a => Bounded (Utf8 a) 
Enum a => Enum (Utf8 a) 
Eq a => Eq (Utf8 a) 
Ord a => Ord (Utf8 a) 
Read a => Read (Utf8 a) 
Show a => Show (Utf8 a) 
IsString a => IsString (Utf8 a) 

newtype Utf16 a Source

Encode a textual value using UTF-16.

Needs to be used with either BigEndian or LittleEndian.

Constructors

Utf16 

Fields

unUtf16 :: a
 

Instances

BuildFrom Builder (Utf16 (LittleEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the LittleEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (LittleEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the LittleEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (BigEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the BigEndian (Utf16 ByteString) instance.

BuildFrom Builder (Utf16 (BigEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the BigEndian (Utf16 ByteString) instance.

BuildFrom Builder (LittleEndian (Utf16 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf16 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf16 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf16 (LittleEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf16 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf16 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf16 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf16 (BigEndian ByteString) instance.

BuildFrom Builder (Utf16 (LittleEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the LittleEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (LittleEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the LittleEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (BigEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the BigEndian (Utf16 Text) instance.

BuildFrom Builder (Utf16 (BigEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the BigEndian (Utf16 Text) instance.

BuildFrom Builder (LittleEndian (Utf16 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf16 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf16 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf16 (LittleEndian Text) instance.

BuildFrom Builder (BigEndian (Utf16 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf16 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf16 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf16 (BigEndian Text) instance.

Bounded a => Bounded (Utf16 a) 
Enum a => Enum (Utf16 a) 
Eq a => Eq (Utf16 a) 
Ord a => Ord (Utf16 a) 
Read a => Read (Utf16 a) 
Show a => Show (Utf16 a) 
IsString a => IsString (Utf16 a) 

newtype Utf32 a Source

Encode a textual value using UTF-32.

Needs to be used with either BigEndian or LittleEndian.

Constructors

Utf32 

Fields

unUtf32 :: a
 

Instances

BuildFrom Builder (Utf32 (LittleEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the LittleEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (LittleEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the LittleEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (BigEndian ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the BigEndian (Utf32 ByteString) instance.

BuildFrom Builder (Utf32 (BigEndian ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the BigEndian (Utf32 ByteString) instance.

BuildFrom Builder (LittleEndian (Utf32 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf32 (LittleEndian ByteString) instance.

BuildFrom Builder (LittleEndian (Utf32 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf32 (LittleEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf32 ByteString))

For lazy ByteStrings; goes via a lazy Text. Equivalent to the Utf32 (BigEndian ByteString) instance.

BuildFrom Builder (BigEndian (Utf32 ByteString))

For strict ByteStrings; goes via a strict Text. Equivalent to the Utf32 (BigEndian ByteString) instance.

BuildFrom Builder (Utf32 (LittleEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the LittleEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (LittleEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the LittleEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (BigEndian Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the BigEndian (Utf32 Text) instance.

BuildFrom Builder (Utf32 (BigEndian Text))

For strict Text values; goes via a strict ByteString. Equivalent to the BigEndian (Utf32 Text) instance.

BuildFrom Builder (LittleEndian (Utf32 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf32 (LittleEndian Text) instance.

BuildFrom Builder (LittleEndian (Utf32 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf32 (LittleEndian Text) instance.

BuildFrom Builder (BigEndian (Utf32 Text))

For lazy Text values; goes via a lazy ByteString. Equivalent to the Utf32 (BigEndian Text) instance.

BuildFrom Builder (BigEndian (Utf32 Text))

For strict Text values; goes via a strict ByteString. Equivalent to the Utf32 (BigEndian Text) instance.

Bounded a => Bounded (Utf32 a) 
Enum a => Enum (Utf32 a) 
Eq a => Eq (Utf32 a) 
Ord a => Ord (Utf32 a) 
Read a => Read (Utf32 a) 
Show a => Show (Utf32 a) 
IsString a => IsString (Utf32 a) 

Text Builders

Both strict and lazy Text values can be constructed via the text Builder, though the latter is preferred.

Values that they can be built from:

  • Strict and lazy Text values.
  • Char and String values directly.
  • Strict and lazy ByteStrings after choosing an appropriate encoding.