text-builder-linear-0.1: Builder for Text based on linear types
Copyright(c) 2022 Andrew Lelechenko
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Text.Builder.Linear.Buffer

Description

Buffer for strict Text, based on linear types.

Synopsis

Documentation

data BufferTYPE ('BoxedRep 'Unlifted) Source #

Internally Buffer is a mutable buffer. If a client gets hold of a variable of type Buffer, they'd be able to pass a mutable buffer to concurrent threads. That's why API below is carefully designed to prevent such possibility: clients always work with linear functions BufferBuffer instead and run them on an empty Buffer to extract results.

In terms of linear-base Buffer is Consumable (see consumeBuffer) and Dupable (see dupBuffer), but not Movable.

>>> :set -XOverloadedStrings -XLinearTypes
>>> import Data.Text.Builder.Linear.Buffer
>>> runBuffer (\b -> '!' .<| "foo" <| (b |> "bar" |>. '.'))
"!foobar."

Remember: this is a strict builder, so on contrary to Data.Text.Lazy.Builder for optimal performance you should use strict left folds instead of lazy right ones.

Starting from GHC 9.2, Buffer is an unlifted datatype, so you can put it into an unboxed tuple (# ..., ... #), but not into (..., ...).

runBuffer ∷ (BufferBuffer) ⊸ Text Source #

Run a linear function on an empty Buffer, producing Text.

Be careful to write runBuffer (b -> ...) instead of runBuffer $ b -> ..., because current implementation of linear types lacks special support for ($). Another option is to enable {-# LANGUAGE BlockArguments #-} and write runBuffer b -> .... Alternatively, you can import Prelude.Linear.($) from linear-base.

runBuffer is similar in spirit to mutable arrays API in Data.Array.Mutable.Linear, which provides functions like fromList ∷ [a] → (Vector aUr b) ⊸ Ur b. Here the initial buffer is always empty and b is Text. Since Text is Movable, Text and Ur Text are equivalent.

dupBufferBuffer ⊸ (# Buffer, Buffer #) Source #

Duplicate builder. Feel free to process results in parallel threads. Similar to Data.Unrestricted.Linear.Dupable from linear-base.

It is a bit tricky to use because of current limitations of linear types with regards to let and where. E. g., one cannot write

let (# b1, b2 #) = dupBuffer b in ("foo" <| b1) >< (b2 |> "bar")

Instead write:

>>> :set -XOverloadedStrings -XLinearTypes -XUnboxedTuples
>>> import Data.Text.Builder.Linear.Buffer
>>> runBuffer (\b -> (\(# b1, b2 #) -> ("foo" <| b1) >< (b2 |> "bar")) (dupBuffer b))
"foobar"

Note the unboxed tuple: starting from GHC 9.2, Buffer is an unlifted datatype, so it cannot be put into (..., ...).

consumeBufferBuffer ⊸ () Source #

Consume buffer linearly, similar to Data.Unrestricted.Linear.Consumable from linear-base.

eraseBufferBufferBuffer Source #

Erase buffer's content, replacing it with an empty Text.

foldlIntoBuffer ∷ (Buffer ⊸ a → Buffer) → Buffer ⊸ [a] → Buffer Source #

This is just a normal foldl', but with a linear arrow and potentially unlifted accumulator.

(|>)BufferTextBuffer infixl 6 Source #

Append Text suffix to a Buffer by mutating it. If a suffix is statically known, consider using (|>#) for optimal performance.

>>> :set -XOverloadedStrings -XLinearTypes
>>> runBuffer (\b -> b |> "foo" |> "bar")
"foobar"

(|>.)BufferCharBuffer infixl 6 Source #

Append Char to a Buffer by mutating it.

>>> :set -XLinearTypes
>>> runBuffer (\b -> b |>. 'q' |>. 'w')
"qw"

(|>#)BufferAddr#Buffer infixl 6 Source #

Append a null-terminated UTF-8 string to a Buffer by mutating it. E. g.,

>>> :set -XOverloadedStrings -XLinearTypes -XMagicHash
>>> runBuffer (\b -> b |># "foo"# |># "bar"#)
"foobar"

The literal string must not contain zero bytes \0, this condition is not checked.

Note the inconsistency in naming: unfortunately, GHC parser does not allow for #<|.

(<|)TextBufferBuffer infixr 6 Source #

Prepend Text prefix to a Buffer by mutating it. If a prefix is statically known, consider using (<|#) for optimal performance.

>>> :set -XOverloadedStrings -XLinearTypes
>>> runBuffer (\b -> "foo" <| "bar" <| b)
"foobar"

(.<|)CharBufferBuffer infixr 6 Source #

Prepend Char to a Buffer by mutating it.

>>> :set -XLinearTypes
>>> runBuffer (\b -> 'q' .<| 'w' .<| b)
"qw"

(<|#)Addr#BufferBuffer infixr 6 Source #

Prepend a null-terminated UTF-8 string to a Buffer by mutating it. E. g.,

>>> :set -XOverloadedStrings -XLinearTypes -XMagicHash
>>> runBuffer (\b -> "foo"# <|# "bar"# <|# b)
"foobar"

The literal string must not contain zero bytes \0, this condition is not checked.

(><)BufferBufferBuffer infix 6 Source #

Concatenate two Buffers, potentially mutating both of them.

You likely need to use dupBuffer to get hold on two builders at once:

>>> :set -XOverloadedStrings -XLinearTypes -XUnboxedTuples
>>> import Data.Text.Builder.Linear.Buffer
>>> runBuffer (\b -> (\(# b1, b2 #) -> ("foo" <| b1) >< (b2 |> "bar")) (dupBuffer b))
"foobar"

(|>$) ∷ (Integral a, FiniteBits a) ⇒ Buffer ⊸ a → Buffer infixl 6 Source #

Append decimal number.

($<|) ∷ (Integral a, FiniteBits a) ⇒ a → BufferBuffer infixr 6 Source #

Prepend decimal number.

(|>%)BufferDoubleBuffer infixl 6 Source #

Append double.

(%<|)DoubleBufferBuffer infixr 6 Source #

Prepend double

(|>&) ∷ (Integral a, FiniteBits a) ⇒ Buffer ⊸ a → Buffer infixl 6 Source #

Append hexadecimal number.

(&<|) ∷ (Integral a, FiniteBits a) ⇒ a → BufferBuffer infixr 6 Source #

Prepend hexadecimal number.

(|>…)BufferWordBuffer infixr 6 Source #

Append given number of spaces.

(…<|)WordBufferBuffer infixr 6 Source #

Prepend given number of spaces.