module Data.Text.Builder.Linear.Buffer (
Buffer,
runBuffer,
runBufferBS,
dupBuffer,
consumeBuffer,
eraseBuffer,
foldlIntoBuffer,
(|>),
(|>.),
(|>#),
(<|),
(.<|),
(<|#),
(><),
(|>$),
($<|),
(|>%),
(%<|),
(|>&),
(&<|),
(|>…),
(…<|),
) where
import Data.Text.Array qualified as A
import Data.Text.Internal (Text (..))
import GHC.Exts (Addr#, Int (..), Ptr (..), cstringLength#, setByteArray#)
import GHC.ST (ST (..))
import Data.Text.Builder.Linear.Char
import Data.Text.Builder.Linear.Core
import Data.Text.Builder.Linear.Dec
import Data.Text.Builder.Linear.Double
import Data.Text.Builder.Linear.Hex
(|>) ∷ Buffer ⊸ Text → Buffer
infixl 6 |>
Buffer
buffer |> :: Buffer %1 -> Text -> Buffer
|> (Text Array
src Int
srcOff Int
srcLen) =
Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
appendExact
Int
srcLen
(\MArray s
dst Int
dstOff → forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
srcLen MArray s
dst Int
dstOff Array
src Int
srcOff)
Buffer
buffer
(<|) ∷ Text → Buffer ⊸ Buffer
infixr 6 <|
Text Array
src Int
srcOff Int
srcLen <| :: Text -> Buffer %1 -> Buffer
<| Buffer
buffer =
Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
prependExact
Int
srcLen
(\MArray s
dst Int
dstOff → forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
srcLen MArray s
dst Int
dstOff Array
src Int
srcOff)
Buffer
buffer
(|>#) ∷ Buffer ⊸ Addr# → Buffer
infixl 6 |>#
Buffer
buffer |># :: Buffer %1 -> Addr# -> Buffer
|># Addr#
addr# =
Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
appendExact
Int
srcLen
(\MArray s
dst Int
dstOff → forall s. MArray s -> Int -> Ptr Word8 -> Int -> ST s ()
A.copyFromPointer MArray s
dst Int
dstOff (forall a. Addr# -> Ptr a
Ptr Addr#
addr#) Int
srcLen)
Buffer
buffer
where
srcLen :: Int
srcLen = Int# -> Int
I# (Addr# -> Int#
cstringLength# Addr#
addr#)
(<|#) ∷ Addr# → Buffer ⊸ Buffer
infixr 6 <|#
Addr#
addr# <|# :: Addr# -> Buffer %1 -> Buffer
<|# Buffer
buffer =
Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
prependExact
Int
srcLen
(\MArray s
dst Int
dstOff → forall s. MArray s -> Int -> Ptr Word8 -> Int -> ST s ()
A.copyFromPointer MArray s
dst Int
dstOff (forall a. Addr# -> Ptr a
Ptr Addr#
addr#) Int
srcLen)
Buffer
buffer
where
srcLen :: Int
srcLen = Int# -> Int
I# (Addr# -> Int#
cstringLength# Addr#
addr#)
(|>…) ∷ Buffer ⊸ Word → Buffer
infixr 6 |>…
Buffer
buf |>… :: Buffer %1 -> Word -> Buffer
|>… Word
0 = Buffer
buf
Buffer
buffer |>… (forall a b. (Integral a, Num b) => a -> b
fromIntegral → spaces :: Int
spaces@(I# Int#
spaces#)) =
Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
appendExact
Int
spaces
( \(A.MutableByteArray MutableByteArray# s
dst#) (I# Int#
dstOff#) →
forall s a. STRep s a -> ST s a
ST
( \State# s
s# →
(# forall d.
MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
setByteArray# MutableByteArray# s
dst# Int#
dstOff# Int#
spaces# Int#
32# State# s
s#, () #)
)
)
Buffer
buffer
(…<|) ∷ Word → Buffer ⊸ Buffer
infixr 6 …<|
Word
0 …<| :: Word -> Buffer %1 -> Buffer
…<| Buffer
buf = Buffer
buf
(forall a b. (Integral a, Num b) => a -> b
fromIntegral → spaces :: Int
spaces@(I# Int#
spaces#)) …<| Buffer
buffer =
Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
prependExact
Int
spaces
( \(A.MutableByteArray MutableByteArray# s
dst#) (I# Int#
dstOff#) →
forall s a. STRep s a -> ST s a
ST
( \State# s
s# →
(# forall d.
MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
setByteArray# MutableByteArray# s
dst# Int#
dstOff# Int#
spaces# Int#
32# State# s
s#, () #)
)
)
Buffer
buffer
foldlIntoBuffer ∷ ∀ a. (Buffer ⊸ a → Buffer) → Buffer ⊸ [a] → Buffer
foldlIntoBuffer :: forall a. (Buffer %1 -> a -> Buffer) -> Buffer %1 -> [a] -> Buffer
foldlIntoBuffer Buffer %1 -> a -> Buffer
f = Buffer %1 -> [a] -> Buffer
go
where
go ∷ Buffer ⊸ [a] → Buffer
go :: Buffer %1 -> [a] -> Buffer
go !Buffer
acc [] = Buffer
acc
go !Buffer
acc (a
x : [a]
xs) = Buffer %1 -> [a] -> Buffer
go (Buffer %1 -> a -> Buffer
f Buffer
acc a
x) [a]
xs