-- |
-- Copyright:   (c) 2022 Andrew Lelechenko
--              (c) 2023 Pierre Le Marre
-- Licence:     BSD3
-- Maintainer:  Andrew Lelechenko <andrew.lelechenko@gmail.com>
--
-- 'Buffer' for strict 'Text', based on linear types.
module Data.Text.Builder.Linear.Buffer (
  -- * Type
  Buffer,

  -- * Basic interface
  runBuffer,
  runBufferBS,
  dupBuffer,
  consumeBuffer,
  eraseBuffer,
  foldlIntoBuffer,
  newEmptyBuffer,
  (><),

  -- * Single character
  (|>.),
  (.<|),

  -- * Multiple characters

  -- ** Character replication
  prependChars,
  appendChars,

  -- ** Text
  (|>),
  (<|),
  (|>…),
  (…<|),

  -- ** Raw 'Addr#'
  (|>#),
  ( #<| ), -- NOTE: extra spaces required because of -XUnboxedTuples
  (<|#),

  -- * Padding
  justifyLeft,
  justifyRight,
  center,

  -- * Number formatting

  -- ** Decimal
  (|>$),
  ($<|),

  -- ** Hexadecimal

  -- *** Lower-case
  (|>&),
  (&<|),

  -- *** Upper-case and padding
  -- $custom_hexadecimal

  -- ** Double
  (|>%),
  (%<|),
) 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

-- | Append 'Text' suffix to a 'Buffer' by mutating it.
-- If a suffix is statically known, consider using '(|>#)' for optimal performance.
--
-- >>> :set -XOverloadedStrings -XLinearTypes
-- >>> runBuffer (\b -> b |> "foo" |> "bar")
-- "foobar"
(|>)  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

-- | Prepend 'Text' prefix to a 'Buffer' by mutating it.
-- If a prefix is statically known, consider using '(#<|)' for optimal performance.
--
-- >>> :set -XOverloadedStrings -XLinearTypes
-- >>> runBuffer (\b -> "foo" <| "bar" <| b)
-- "foobar"
(<|)  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

-- | 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.
(|>#)  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#)

-- | 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.
--
-- /Note:/ When the syntactic extensions @UnboxedTuples@ or @UnboxedSums@ are
-- enabled, extra spaces are required when using parentheses: i.e. use @( '#<|' )@
-- instead of @('#<|')@. See the GHC User Guide chapter
-- “[Unboxed types and primitive operations](https://downloads.haskell.org/ghc/latest/docs/users_guide/exts/primitives.html#unboxed-tuples)”
-- for further information.
( #<| )  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#)

-- | Alias for @'(#<|)'@.
{-# DEPRECATED (<|#) "Use '(#<|)' instead" #-}
(<|#)  Addr#  Buffer  Buffer
<|# :: Addr# -> Buffer %1 -> Buffer
(<|#) = ( #<| ) -- NOTE: extra spaces required because of -XUnboxedTuples
{-# INLINE (<|#) #-}

-- | Append given number of spaces.
(|>…)  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

-- | Prepend given number of spaces.
(…<|)  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

-- | This is just a normal 'Data.List.foldl'', but with a linear arrow
-- and unlifted accumulator.
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

-- $custom_hexadecimal
--
-- Note that no /upper/ case hexadecimal formatting is provided. This package
-- provides a minimal API with utility functions only for common cases. For
-- other use cases, please adapt the code of this package, e.g. as shown in
-- the [Unicode code point example](https://github.com/Bodigrim/linear-builder/examples/src/Examples/Unicode.hs).