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

Description

Low-level routines for Buffer manipulations.

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.

byteSizeOfBufferBuffer ⊸ (# Buffer, Word #) Source #

Return buffer's size in bytes (not in Chars). This could be useful to implement a lazy builder atop of a strict one.

lengthOfBufferBuffer ⊸ (# Buffer, Word #) Source #

Return buffer's length in Chars (not in bytes). This could be useful to implement dropEndBuffer and takeEndBuffer, e. g.,

import Data.Unrestricted.Linear

dropEndBuffer :: Word -> Buffer %1 -> Buffer
dropEndBuffer n buf =
  ((# buf', len #) -> case move len of Ur len' -> takeBuffer (len' - n) buf')
    (lengthOfBuffer buf)

dropBufferWordBufferBuffer Source #

Slice Buffer by dropping given number of Chars.

takeBufferWordBufferBuffer Source #

Slice Buffer by taking given number of Chars.

appendBounded Source #

Arguments

Int

Upper bound for the number of bytes, written by an action

→ (∀ s. MArray s → IntST s Int)

Action, which writes bytes starting from the given offset and returns an actual number of bytes written.

Buffer 
Buffer 

Low-level routine to append data of unknown size to a Buffer.

appendExact Source #

Arguments

Int

Exact number of bytes, written by an action

→ (∀ s. MArray s → IntST s ())

Action, which writes bytes starting from the given offset

Buffer 
Buffer 

Low-level routine to append data of known size to a Buffer.

prependBounded Source #

Arguments

Int

Upper bound for the number of bytes, written by an action

→ (∀ s. MArray s → IntST s Int)

Action, which writes bytes finishing before the given offset and returns an actual number of bytes written.

→ (∀ s. MArray s → IntST s Int)

Action, which writes bytes starting from the given offset and returns an actual number of bytes written.

Buffer 
Buffer 

Low-level routine to prepend data of unknown size to a Buffer.

prependExact Source #

Arguments

Int

Exact number of bytes, written by an action

→ (∀ s. MArray s → IntST s ())

Action, which writes bytes starting from the given offset

Buffer 
Buffer 

Low-level routine to append data of unknown size to a Buffer.

(><)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"