| Copyright | (c) 2022 Andrew Lelechenko |
|---|---|
| License | BSD3 |
| Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Text.Builder.Linear.Buffer
Synopsis
- data Buffer ∷ TYPE ('BoxedRep 'Unlifted)
- runBuffer ∷ (Buffer ⊸ Buffer) ⊸ Text
- dupBuffer ∷ Buffer ⊸ (# Buffer, Buffer #)
- consumeBuffer ∷ Buffer ⊸ ()
- eraseBuffer ∷ Buffer ⊸ Buffer
- foldlIntoBuffer ∷ (Buffer ⊸ a → Buffer) → Buffer ⊸ [a] → Buffer
- (|>) ∷ Buffer ⊸ Text → Buffer
- (|>.) ∷ Buffer ⊸ Char → Buffer
- (|>#) ∷ Buffer ⊸ Addr# → Buffer
- (<|) ∷ Text → Buffer ⊸ Buffer
- (.<|) ∷ Char → Buffer ⊸ Buffer
- (<|#) ∷ Addr# → Buffer ⊸ Buffer
- (><) ∷ Buffer ⊸ Buffer ⊸ Buffer
- (|>$) ∷ (Integral a, FiniteBits a) ⇒ Buffer ⊸ a → Buffer
- ($<|) ∷ (Integral a, FiniteBits a) ⇒ a → Buffer ⊸ Buffer
- (|>%) ∷ Buffer ⊸ Double → Buffer
- (%<|) ∷ Double → Buffer ⊸ Buffer
- (|>&) ∷ (Integral a, FiniteBits a) ⇒ Buffer ⊸ a → Buffer
- (&<|) ∷ (Integral a, FiniteBits a) ⇒ a → Buffer ⊸ Buffer
- (|>…) ∷ Buffer ⊸ Word → Buffer
- (…<|) ∷ Word → Buffer ⊸ Buffer
Documentation
data Buffer ∷ TYPE ('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 Buffer ⊸ Buffer 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 ∷ (Buffer ⊸ Buffer) ⊸ 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 a ⊸ Ur b) ⊸ Ur b.
Here the initial buffer is always empty and b is Text. Since Text is Movable,
Text and Ur Text are equivalent.
dupBuffer ∷ Buffer ⊸ (# 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 (..., ...).
consumeBuffer ∷ Buffer ⊸ () Source #
Consume buffer linearly,
similar to Data.Unrestricted.Linear.Consumable from linear-base.
foldlIntoBuffer ∷ (Buffer ⊸ a → Buffer) → Buffer ⊸ [a] → Buffer Source #
This is just a normal foldl', but with a linear arrow
and potentially unlifted accumulator.
(|>#) ∷ Buffer ⊸ Addr# → 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 #<|.
(<|#) ∷ Addr# → Buffer ⊸ Buffer 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.
(><) ∷ Buffer ⊸ Buffer ⊸ Buffer 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 hexadecimal number.