Copyright | (c) 2022 Andrew Lelechenko (c) 2023 Pierre Le Marre |
---|---|
License | BSD3 |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Low-level routines for Buffer
manipulations.
Synopsis
- data Buffer :: TYPE ('BoxedRep 'Unlifted)
- runBuffer :: (Buffer %1 -> Buffer) %1 -> Text
- runBufferBS :: (Buffer %1 -> Buffer) %1 -> ByteString
- dupBuffer :: Buffer %1 -> (# Buffer, Buffer #)
- consumeBuffer :: Buffer %1 -> ()
- eraseBuffer :: Buffer %1 -> Buffer
- byteSizeOfBuffer :: Buffer %1 -> (# Buffer, Word #)
- lengthOfBuffer :: Buffer %1 -> (# Buffer, Word #)
- dropBuffer :: Word -> Buffer %1 -> Buffer
- takeBuffer :: Word -> Buffer %1 -> Buffer
- newEmptyBuffer :: Buffer %1 -> (# Buffer, Buffer #)
- appendBounded :: Int -> (forall s. MArray s -> Int -> ST s Int) -> Buffer %1 -> Buffer
- appendExact :: Int -> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
- prependBounded :: Int -> (forall s. MArray s -> Int -> ST s Int) -> (forall s. MArray s -> Int -> ST s Int) -> Buffer %1 -> Buffer
- prependExact :: Int -> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
- (><) :: Buffer %1 -> Buffer %1 -> Buffer
Type
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.
Buffer
is an unlifted datatype,
so you can put it into an unboxed tuple (# ..., ... #)
,
but not into (..., ...)
.
Basic interface
runBuffer :: (Buffer %1 -> Buffer) %1 -> Text Source #
Run a linear function on an empty Buffer
, producing a strict 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
($)
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.
runBufferBS :: (Buffer %1 -> Buffer) %1 -> ByteString Source #
Same as runBuffer
, but returning a UTF-8 encoded strict ByteString
.
dupBuffer :: Buffer %1 -> (# Buffer, Buffer #) Source #
Duplicate builder. Feel free to process results in parallel threads.
Similar to
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 -> case dupBuffer b of (# b1, b2 #) -> ("foo" <| b1) >< (b2 |> "bar"))
"foobar"
Note the unboxed tuple: Buffer
is an unlifted datatype,
so it cannot be put into (..., ...)
.
consumeBuffer :: Buffer %1 -> () Source #
Consume buffer linearly,
similar to
Consumable
from linear-base
.
byteSizeOfBuffer :: Buffer %1 -> (# Buffer, Word #) Source #
Return buffer's size in bytes (not in Char
s).
This could be useful to implement a lazy builder atop of a strict one.
lengthOfBuffer :: Buffer %1 -> (# Buffer, Word #) Source #
Return buffer's length in Char
s (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 = case lengthOfBuffer buf of (# buf', len #) -> case move len of Ur len' -> takeBuffer (len' - n) buf'
newEmptyBuffer :: Buffer %1 -> (# Buffer, Buffer #) Source #
Create an empty Buffer
.
The first Buffer
is the input and the second is a new empty Buffer
.
This function is needed in some situations, e.g. with
justifyRight
. The following example creates
a utility function that justify a text and then append it to a buffer.
>>>
:set -XOverloadedStrings -XLinearTypes -XUnboxedTuples
>>>
import Data.Text.Builder.Linear.Buffer
>>>
import Data.Text (Text)
>>>
:{
appendJustified :: Buffer %1 -> Text -> Buffer appendJustified b t = case newEmptyBuffer b of -- Note that we need to create a new buffer from the text, in order -- to justify only the text and not the input buffer. (# b', empty #) -> b' >< justifyRight 12 ' ' (empty |> t) :}
>>>
runBuffer (\b -> (b |> "Test:") `appendJustified` "AAA" `appendJustified` "BBBBBBB")
"Test: AAA BBBBBBB"
Note: a previous buffer is necessary in order to create an empty buffer with the same characteristics.
Text concatenation
:: Int | Upper bound for the number of bytes, written by an action |
-> (forall s. MArray s -> Int -> ST 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
.
:: Int | Exact number of bytes, written by an action |
-> (forall s. MArray s -> Int -> ST s ()) | Action, which writes bytes starting from the given offset |
-> Buffer | |
-> Buffer |
Low-level routine to append data of known size to a Buffer
.
:: Int | Upper bound for the number of bytes, written by an action |
-> (forall s. MArray s -> Int -> ST s Int) | Action, which writes bytes finishing before the given offset and returns an actual number of bytes written. |
-> (forall s. MArray s -> Int -> ST 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
.
:: Int | Exact number of bytes, written by an action |
-> (forall s. MArray s -> Int -> ST s ()) | Action, which writes bytes starting from the given offset |
-> Buffer | |
-> Buffer |
Low-level routine to append data of known size to a Buffer
.
(><) :: Buffer %1 -> Buffer %1 -> Buffer infix 6 Source #
Concatenate two Buffer
s, 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 -> case dupBuffer b of (# b1, b2 #) -> ("foo" <| b1) >< (b2 |> "bar"))
"foobar"