Copyright | (c) 2022 Andrew Lelechenko |
---|---|
License | BSD3 |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
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
- foldlIntoBuffer :: forall a. (Buffer %1 -> a -> Buffer) -> Buffer %1 -> [a] -> Buffer
- (|>) :: Buffer %1 -> Text -> Buffer
- (|>.) :: Buffer %1 -> Char -> Buffer
- (|>#) :: Buffer %1 -> Addr# -> Buffer
- (<|) :: Text -> Buffer %1 -> Buffer
- (.<|) :: Char -> Buffer %1 -> Buffer
- (<|#) :: Addr# -> Buffer %1 -> Buffer
- (><) :: Buffer %1 -> Buffer %1 -> Buffer
- (|>$) :: (Integral a, FiniteBits a) => Buffer %1 -> a -> Buffer
- ($<|) :: (Integral a, FiniteBits a) => a -> Buffer %1 -> Buffer
- (|>%) :: Buffer %1 -> Double -> Buffer
- (%<|) :: Double -> Buffer %1 -> Buffer
- (|>&) :: (Integral a, FiniteBits a) => Buffer %1 -> a -> Buffer
- (&<|) :: (Integral a, FiniteBits a) => a -> Buffer %1 -> Buffer
- (|>…) :: Buffer %1 -> Word -> Buffer
- (…<|) :: Word -> Buffer %1 -> 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.
Buffer
is an unlifted datatype,
so you can put it into an unboxed tuple (# ..., ... #)
,
but not into (..., ...)
.
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 -> (\(# b1, b2 #) -> ("foo" <| b1) >< (b2 |> "bar")) (dupBuffer b))
"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
.
foldlIntoBuffer :: forall a. (Buffer %1 -> a -> Buffer) -> Buffer %1 -> [a] -> Buffer Source #
This is just a normal foldl'
, but with a linear arrow
and unlifted accumulator.
(|>#) :: Buffer %1 -> 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
and must be a valid UTF-8,
these conditions are not checked.
Note the inconsistency in naming: unfortunately, GHC parser does not allow for #<|
.
(<|#) :: Addr# -> Buffer %1 -> 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
and must be a valid UTF-8,
these conditions are not checked.
(><) :: 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 -> (\(# b1, b2 #) -> ("foo" <| b1) >< (b2 |> "bar")) (dupBuffer b))
"foobar"
(|>$) :: (Integral a, FiniteBits a) => Buffer %1 -> a -> Buffer infixl 6 Source #
Append decimal number.
($<|) :: (Integral a, FiniteBits a) => a -> Buffer %1 -> Buffer infixr 6 Source #
Prepend decimal number.
(|>&) :: (Integral a, FiniteBits a) => Buffer %1 -> a -> Buffer infixl 6 Source #
Append hexadecimal number.