-- |
-- Copyright:   (c) 2022 Andrew Lelechenko
-- Licence:     BSD3
-- Maintainer:  Andrew Lelechenko <andrew.lelechenko@gmail.com>
--
-- Low-level routines for 'Buffer' manipulations.

module Data.Text.Builder.Linear.Core
  ( Buffer
  , runBuffer
  , dupBuffer
  , consumeBuffer
  , eraseBuffer
  , byteSizeOfBuffer
  , lengthOfBuffer
  , dropBuffer
  , takeBuffer
  , appendBounded
  , appendExact
  , prependBounded
  , prependExact
  , (><)
  ) where

import qualified Data.Text as T
import Data.Text.Array (Array(..), MArray(..))
import qualified Data.Text.Array as A
import Data.Text.Internal (Text(..))
import GHC.Exts (unsafeCoerce#, Int(..), sizeofByteArray#)
#if MIN_VERSION_base(4,16,0)
import GHC.Exts (TYPE, Levity(..), RuntimeRep(..))
#endif
import GHC.ST (ST(..), runST)

-- | 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 @(..., ...)@.
--
#if MIN_VERSION_base(4,16,0)
data Buffer  TYPE ('BoxedRep 'Unlifted) where
#else
data Buffer where
#endif
  Buffer  {-# UNPACK #-} !Text  Buffer

-- | Unwrap 'Buffer', no-op.
-- Most likely, this is not the function you're looking for
-- and you need 'runBuffer' instead.
unBuffer  Buffer  Text
unBuffer :: Buffer %1 -> Text
unBuffer (Buffer Text
x) = Text
x

-- | 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.
--
runBuffer  (Buffer  Buffer)  Text
runBuffer :: (Buffer %1 -> Buffer) %1 -> Text
runBuffer Buffer %1 -> Buffer
f = Buffer %1 -> Text
unBuffer (Buffer %1 -> Buffer
f (Text -> Buffer
Buffer Text
forall a. Monoid a => a
mempty))

-- | 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
-- <https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/linear_types.html#limitations 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 @(..., ...)@.
--
dupBuffer  Buffer  (# Buffer, Buffer #)
dupBuffer :: Buffer %1 -> (# Buffer, Buffer #)
dupBuffer (Buffer Text
x) = (# Text -> Buffer
Buffer Text
x, Text -> Buffer
Buffer (Text -> Text
T.copy Text
x) #)

-- | Consume buffer linearly,
-- similar to @Data.Unrestricted.Linear.Consumable@ from @linear-base@.
consumeBuffer  Buffer  ()
consumeBuffer :: Buffer %1 -> ()
consumeBuffer Buffer{} = ()

-- | Erase buffer's content, replacing it with an empty 'Text'.
eraseBuffer  Buffer  Buffer
eraseBuffer :: Buffer %1 -> Buffer
eraseBuffer Buffer{} = Text -> Buffer
Buffer Text
forall a. Monoid a => a
mempty

-- | Return buffer's size in __bytes__ (not in 'Char's).
-- This could be useful to implement a lazy builder atop of a strict one.
byteSizeOfBuffer  Buffer  (# Buffer, Word #)
byteSizeOfBuffer :: Buffer %1 -> (# Buffer, Word #)
byteSizeOfBuffer (Buffer t :: Text
t@(Text Array
_ Int
_ Int
len)) = (# Text -> Buffer
Buffer Text
t, Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len #)

-- | 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 =
--   (\(# buf', len #) -> case move len of Ur len' -> takeBuffer (len' - n) buf')
--     (lengthOfBuffer buf)
-- @
lengthOfBuffer  Buffer  (# Buffer, Word #)
lengthOfBuffer :: Buffer %1 -> (# Buffer, Word #)
lengthOfBuffer (Buffer Text
t) = (# Text -> Buffer
Buffer Text
t, Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Text -> Int
T.length Text
t) #)

-- | Slice 'Buffer' by dropping given number of 'Char's.
dropBuffer  Word  Buffer  Buffer
dropBuffer :: Word -> Buffer %1 -> Buffer
dropBuffer Word
nChar (Buffer t :: Text
t@(Text Array
arr Int
off Int
len))
  | Int
nByte Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Text -> Buffer
Buffer (Array -> Int -> Int -> Text
Text Array
arr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) Int
0)
  | Bool
otherwise = Text -> Buffer
Buffer (Array -> Int -> Int -> Text
Text Array
arr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
nByte) (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nByte))
  where
    nByte :: Int
nByte = Int -> Text -> Int
T.measureOff (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
nChar) Text
t

-- | Slice 'Buffer' by taking given number of 'Char's.
takeBuffer  Word  Buffer  Buffer
takeBuffer :: Word -> Buffer %1 -> Buffer
takeBuffer Word
nChar (Buffer t :: Text
t@(Text Array
arr Int
off Int
_))
  | Int
nByte Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Text -> Buffer
Buffer Text
t
  | Bool
otherwise = Text -> Buffer
Buffer (Array -> Int -> Int -> Text
Text Array
arr Int
off Int
nByte)
  where
    nByte :: Int
nByte = Int -> Text -> Int
T.measureOff (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
nChar) Text
t

-- | Low-level routine to append data of unknown size to a 'Buffer'.
appendBounded
   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
appendBounded :: Int
-> (forall s. MArray s -> Int -> ST s Int) -> Buffer %1 -> Buffer
appendBounded Int
maxSrcLen forall s. MArray s -> Int -> ST s Int
appender (Buffer (Text Array
dst Int
dstOff Int
dstLen)) = Text -> Buffer
Buffer (Text -> Buffer) -> Text -> Buffer
forall a b. (a -> b) -> a -> b
$ (forall s. ST s Text) -> Text
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s Text) -> Text) -> (forall s. ST s Text) -> Text
forall a b. (a -> b) -> a -> b
$ do
  let dstFullLen :: Int
dstFullLen = Array -> Int
sizeofByteArray Array
dst
      newFullLen :: Int
newFullLen = Int
dstOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
dstLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
maxSrcLen)
  MArray s
newM  if Int
dstOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dstLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
maxSrcLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
dstFullLen
    then Array -> ST s (MArray s)
forall s. Array -> ST s (MArray s)
unsafeThaw Array
dst
    else do
      MArray s
tmpM  Int -> ST s (MArray s)
forall s. Int -> ST s (MArray s)
A.new Int
newFullLen
      Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
dstLen MArray s
tmpM Int
dstOff Array
dst Int
dstOff
      MArray s -> ST s (MArray s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure MArray s
tmpM
  Int
srcLen  MArray s -> Int -> ST s Int
forall s. MArray s -> Int -> ST s Int
appender MArray s
newM (Int
dstOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dstLen)
  Array
new  MArray s -> ST s Array
forall s. MArray s -> ST s Array
A.unsafeFreeze MArray s
newM
  Text -> ST s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ST s Text) -> Text -> ST s Text
forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
Text Array
new Int
dstOff (Int
dstLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
srcLen)
{-# INLINE appendBounded #-}

-- | Low-level routine to append data of known size to a 'Buffer'.
appendExact
   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
appendExact :: Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
appendExact Int
srcLen forall s. MArray s -> Int -> ST s ()
appender = Int
-> (forall s. MArray s -> Int -> ST s Int) -> Buffer %1 -> Buffer
appendBounded
  Int
srcLen
  (\MArray s
dst Int
dstOff  MArray s -> Int -> ST s ()
forall s. MArray s -> Int -> ST s ()
appender MArray s
dst Int
dstOff ST s () -> ST s Int -> ST s Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
srcLen)
{-# INLINE appendExact #-}

-- | Low-level routine to prepend data of unknown size to a 'Buffer'.
prependBounded
   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
prependBounded :: Int
-> (forall s. MArray s -> Int -> ST s Int)
-> (forall s. MArray s -> Int -> ST s Int)
-> Buffer
%1 -> Buffer
prependBounded Int
maxSrcLen forall s. MArray s -> Int -> ST s Int
prepender forall s. MArray s -> Int -> ST s Int
appender (Buffer (Text Array
dst Int
dstOff Int
dstLen))
  | Int
maxSrcLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
dstOff = Text -> Buffer
Buffer (Text -> Buffer) -> Text -> Buffer
forall a b. (a -> b) -> a -> b
$ (forall s. ST s Text) -> Text
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s Text) -> Text) -> (forall s. ST s Text) -> Text
forall a b. (a -> b) -> a -> b
$ do
    MArray s
newM  Array -> ST s (MArray s)
forall s. Array -> ST s (MArray s)
unsafeThaw Array
dst
    Int
srcLen  MArray s -> Int -> ST s Int
forall s. MArray s -> Int -> ST s Int
prepender MArray s
newM Int
dstOff
    Array
new  MArray s -> ST s Array
forall s. MArray s -> ST s Array
A.unsafeFreeze MArray s
newM
    Text -> ST s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ST s Text) -> Text -> ST s Text
forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
Text Array
new (Int
dstOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
srcLen) (Int
srcLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dstLen)
  | Bool
otherwise = Text -> Buffer
Buffer (Text -> Buffer) -> Text -> Buffer
forall a b. (a -> b) -> a -> b
$ (forall s. ST s Text) -> Text
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s Text) -> Text) -> (forall s. ST s Text) -> Text
forall a b. (a -> b) -> a -> b
$ do
    let dstFullLen :: Int
dstFullLen = Array -> Int
sizeofByteArray Array
dst
        newOff :: Int
newOff = Int
dstLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
maxSrcLen
        newFullLen :: Int
newFullLen = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
newOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
dstFullLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
dstOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
dstLen)
    MArray s
newM  Int -> ST s (MArray s)
forall s. Int -> ST s (MArray s)
A.new Int
newFullLen
    Int
srcLen  MArray s -> Int -> ST s Int
forall s. MArray s -> Int -> ST s Int
appender MArray s
newM Int
newOff
    Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
dstLen MArray s
newM (Int
newOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
srcLen) Array
dst Int
dstOff
    Array
new  MArray s -> ST s Array
forall s. MArray s -> ST s Array
A.unsafeFreeze MArray s
newM
    Text -> ST s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ST s Text) -> Text -> ST s Text
forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
Text Array
new Int
newOff (Int
dstLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
srcLen)
{-# INLINE prependBounded #-}

-- | Low-level routine to append data of unknown size to a 'Buffer'.
prependExact
   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
prependExact :: Int
-> (forall s. MArray s -> Int -> ST s ()) -> Buffer %1 -> Buffer
prependExact Int
srcLen forall s. MArray s -> Int -> ST s ()
appender = Int
-> (forall s. MArray s -> Int -> ST s Int)
-> (forall s. MArray s -> Int -> ST s Int)
-> Buffer
%1 -> Buffer
prependBounded
  Int
srcLen
  (\MArray s
dst Int
dstOff  MArray s -> Int -> ST s ()
forall s. MArray s -> Int -> ST s ()
appender MArray s
dst (Int
dstOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
srcLen) ST s () -> ST s Int -> ST s Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
srcLen)
  (\MArray s
dst Int
dstOff  MArray s -> Int -> ST s ()
forall s. MArray s -> Int -> ST s ()
appender MArray s
dst Int
dstOff ST s () -> ST s Int -> ST s Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
srcLen)
{-# INLINE prependExact #-}

unsafeThaw  Array  ST s (MArray s)
unsafeThaw :: forall s. Array -> ST s (MArray s)
unsafeThaw (ByteArray ByteArray#
a) = STRep s (MArray s) -> ST s (MArray s)
forall s a. STRep s a -> ST s a
ST (STRep s (MArray s) -> ST s (MArray s))
-> STRep s (MArray s) -> ST s (MArray s)
forall a b. (a -> b) -> a -> b
$ \State# s
s# 
  (# State# s
s#, MutableByteArray# s -> MArray s
forall s. MutableByteArray# s -> MArray s
MutableByteArray (ByteArray# -> MutableByteArray# s
unsafeCoerce# ByteArray#
a) #)

sizeofByteArray  Array  Int
sizeofByteArray :: Array -> Int
sizeofByteArray (ByteArray ByteArray#
a) = Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
a)

-- | 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"
--
(><)  Buffer  Buffer  Buffer
infix 6 ><
Buffer (Text Array
left Int
leftOff Int
leftLen) >< :: Buffer %1 -> Buffer %1 -> Buffer
>< Buffer (Text Array
right Int
rightOff Int
rightLen) = Text -> Buffer
Buffer (Text -> Buffer) -> Text -> Buffer
forall a b. (a -> b) -> a -> b
$ (forall s. ST s Text) -> Text
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s Text) -> Text) -> (forall s. ST s Text) -> Text
forall a b. (a -> b) -> a -> b
$ do
  let leftFullLen :: Int
leftFullLen = Array -> Int
sizeofByteArray Array
left
      rightFullLen :: Int
rightFullLen = Array -> Int
sizeofByteArray Array
right
      canCopyToLeft :: Bool
canCopyToLeft = Int
leftOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leftLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
leftFullLen
      canCopyToRight :: Bool
canCopyToRight = Int
leftLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
rightOff
      shouldCopyToLeft :: Bool
shouldCopyToLeft = Bool
canCopyToLeft Bool -> Bool -> Bool
&& (Bool -> Bool
not Bool
canCopyToRight Bool -> Bool -> Bool
|| Int
leftLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
rightLen)
  if Bool
shouldCopyToLeft then do
    MArray s
newM  Array -> ST s (MArray s)
forall s. Array -> ST s (MArray s)
unsafeThaw Array
left
    Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
rightLen MArray s
newM (Int
leftOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leftLen) Array
right Int
rightOff
    Array
new  MArray s -> ST s Array
forall s. MArray s -> ST s Array
A.unsafeFreeze MArray s
newM
    Text -> ST s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ST s Text) -> Text -> ST s Text
forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
Text Array
new Int
leftOff (Int
leftLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightLen)
  else if Bool
canCopyToRight then do
    MArray s
newM  Array -> ST s (MArray s)
forall s. Array -> ST s (MArray s)
unsafeThaw Array
right
    Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
leftLen MArray s
newM (Int
rightOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
leftLen) Array
left Int
leftOff
    Array
new  MArray s -> ST s Array
forall s. MArray s -> ST s Array
A.unsafeFreeze MArray s
newM
    Text -> ST s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ST s Text) -> Text -> ST s Text
forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
Text Array
new (Int
rightOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
leftLen) (Int
leftLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightLen)
  else do
    let fullLen :: Int
fullLen = Int
leftOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leftLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
rightFullLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rightOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rightLen)
    MArray s
newM  Int -> ST s (MArray s)
forall s. Int -> ST s (MArray s)
A.new Int
fullLen
    Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
leftLen MArray s
newM Int
leftOff Array
left Int
leftOff
    Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
A.copyI Int
rightLen MArray s
newM (Int
leftOff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leftLen) Array
right Int
rightOff
    Array
new  MArray s -> ST s Array
forall s. MArray s -> ST s Array
A.unsafeFreeze MArray s
newM
    Text -> ST s Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ST s Text) -> Text -> ST s Text
forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
Text Array
new Int
leftOff (Int
leftLen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightLen)