{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-unused-imports #-}
module TextBuilderDev.Allocator
(
allocate,
sizeBound,
Allocator,
force,
text,
asciiByteString,
char,
unicodeCodePoint,
utf8CodeUnits1,
utf8CodeUnits2,
utf8CodeUnits3,
utf8CodeUnits4,
utf16CodeUnits1,
utf16CodeUnits2,
finiteBitsUnsignedBinary,
fixedUnsignedDecimal,
)
where
import qualified Data.ByteString as ByteString
import qualified Data.Text as Text
import qualified Data.Text.Array as TextArray
import qualified Data.Text.IO as Text
import qualified Data.Text.Internal as TextInternal
import qualified Data.Text.Lazy as TextLazy
import qualified Data.Text.Lazy.Builder as TextLazyBuilder
import TextBuilderDev.Prelude
import qualified TextBuilderDev.Utf16View as Utf16View
import qualified TextBuilderDev.Utf8View as Utf8View
newtype ArrayWriter
= ArrayWriter (forall s. TextArray.MArray s -> Int -> ST s Int)
instance Semigroup ArrayWriter where
{-# INLINE (<>) #-}
ArrayWriter forall s. MArray s -> Int -> ST s Int
writeL <> :: ArrayWriter -> ArrayWriter -> ArrayWriter
<> ArrayWriter forall s. MArray s -> Int -> ST s Int
writeR =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
array Int
offset -> do
Int
offsetAfter1 <- forall s. MArray s -> Int -> ST s Int
writeL MArray s
array Int
offset
forall s. MArray s -> Int -> ST s Int
writeR MArray s
array Int
offsetAfter1
stimes :: forall b. Integral b => b -> ArrayWriter -> ArrayWriter
stimes b
n (ArrayWriter forall s. MArray s -> Int -> ST s Int
write) =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
array ->
let go :: b -> Int -> ST s Int
go b
n Int
offset =
if b
n forall a. Ord a => a -> a -> Bool
> b
0
then do
Int
offset <- forall s. MArray s -> Int -> ST s Int
write MArray s
array Int
offset
b -> Int -> ST s Int
go (forall a. Enum a => a -> a
pred b
n) Int
offset
else forall (m :: * -> *) a. Monad m => a -> m a
return Int
offset
in b -> Int -> ST s Int
go b
n
instance Monoid ArrayWriter where
{-# INLINE mempty #-}
mempty :: ArrayWriter
mempty = (forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return
allocate :: Allocator -> Text
allocate :: Allocator -> Text
allocate (Allocator (ArrayWriter forall s. MArray s -> Int -> ST s Int
write) Int
sizeBound) =
forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
MArray s
array <- forall s. Int -> ST s (MArray s)
TextArray.new Int
sizeBound
Int
offsetAfter <- forall s. MArray s -> Int -> ST s Int
write MArray s
array Int
0
Array
frozenArray <- forall s. MArray s -> ST s Array
TextArray.unsafeFreeze MArray s
array
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Array -> Int -> Int -> Text
TextInternal.text Array
frozenArray Int
0 Int
offsetAfter
sizeBound :: Allocator -> Int
sizeBound :: Allocator -> Int
sizeBound (Allocator ArrayWriter
_ Int
sizeBound) = Int
sizeBound
data Allocator
= Allocator
!ArrayWriter
{-# UNPACK #-} !Int
instance Semigroup Allocator where
{-# INLINE (<>) #-}
<> :: Allocator -> Allocator -> Allocator
(<>) (Allocator ArrayWriter
writer1 Int
estimatedArraySize1) (Allocator ArrayWriter
writer2 Int
estimatedArraySize2) =
ArrayWriter -> Int -> Allocator
Allocator ArrayWriter
writer Int
estimatedArraySize
where
writer :: ArrayWriter
writer = ArrayWriter
writer1 forall a. Semigroup a => a -> a -> a
<> ArrayWriter
writer2
estimatedArraySize :: Int
estimatedArraySize = Int
estimatedArraySize1 forall a. Num a => a -> a -> a
+ Int
estimatedArraySize2
stimes :: forall b. Integral b => b -> Allocator -> Allocator
stimes b
n (Allocator ArrayWriter
writer Int
sizeBound) =
ArrayWriter -> Int -> Allocator
Allocator
(forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n ArrayWriter
writer)
(Int
sizeBound forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral b
n)
instance Monoid Allocator where
{-# INLINE mempty #-}
mempty :: Allocator
mempty = ArrayWriter -> Int -> Allocator
Allocator forall a. Monoid a => a
mempty Int
0
{-# INLINE force #-}
force :: Allocator -> Allocator
force :: Allocator -> Allocator
force = Text -> Allocator
text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Allocator -> Text
allocate
{-# INLINE sizedWriter #-}
sizedWriter :: Int -> (forall s. TextArray.MArray s -> Int -> ST s Int) -> Allocator
sizedWriter :: Int -> (forall s. MArray s -> Int -> ST s Int) -> Allocator
sizedWriter Int
size forall s. MArray s -> Int -> ST s Int
write =
ArrayWriter -> Int -> Allocator
Allocator ((forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall s. MArray s -> Int -> ST s Int
write) Int
size
{-# INLINEABLE text #-}
text :: Text -> Allocator
#if MIN_VERSION_text(2,0,0)
text text@(TextInternal.Text array offset length) =
Allocator writer length
where
writer =
ArrayWriter $ \builderArray builderOffset -> do
TextArray.copyI length builderArray builderOffset array offset
return $ builderOffset + length
#else
text :: Text -> Allocator
text text :: Text
text@(TextInternal.Text Array
array Int
offset Int
length) =
ArrayWriter -> Int -> Allocator
Allocator ArrayWriter
writer Int
length
where
writer :: ArrayWriter
writer =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
builderArray Int
builderOffset -> do
let builderOffsetAfter :: Int
builderOffsetAfter = Int
builderOffset forall a. Num a => a -> a -> a
+ Int
length
forall s. MArray s -> Int -> Array -> Int -> Int -> ST s ()
TextArray.copyI MArray s
builderArray Int
builderOffset Array
array Int
offset Int
builderOffsetAfter
forall (m :: * -> *) a. Monad m => a -> m a
return Int
builderOffsetAfter
#endif
{-# INLINEABLE asciiByteString #-}
asciiByteString :: ByteString -> Allocator
asciiByteString :: ByteString -> Allocator
asciiByteString ByteString
byteString =
ArrayWriter -> Int -> Allocator
Allocator ArrayWriter
action Int
length
where
length :: Int
length = ByteString -> Int
ByteString.length ByteString
byteString
action :: ArrayWriter
action =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
array ->
let step :: Word8 -> (Int -> ST s Int) -> Int -> ST s Int
step Word8
byte Int -> ST s Int
next Int
index = do
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array Int
index (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
byte)
Int -> ST s Int
next (forall a. Enum a => a -> a
succ Int
index)
in forall a. (Word8 -> a -> a) -> a -> ByteString -> a
ByteString.foldr Word8 -> (Int -> ST s Int) -> Int -> ST s Int
step forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
byteString
{-# INLINE char #-}
char :: Char -> Allocator
char :: Char -> Allocator
char = Int -> Allocator
unicodeCodePoint forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Char -> Int
ord
{-# INLINE unicodeCodePoint #-}
unicodeCodePoint :: Int -> Allocator
#if MIN_VERSION_text(2,0,0)
unicodeCodePoint x =
Utf8View.unicodeCodePoint x utf8CodeUnits1 utf8CodeUnits2 utf8CodeUnits3 utf8CodeUnits4
#else
unicodeCodePoint :: Int -> Allocator
unicodeCodePoint Int
x =
Int -> Utf16View
Utf16View.unicodeCodePoint Int
x Word16 -> Allocator
utf16CodeUnits1 Word16 -> Word16 -> Allocator
utf16CodeUnits2
#endif
utf8CodeUnits1 :: Word8 -> Allocator
#if MIN_VERSION_text(2,0,0)
{-# INLINEABLE utf8CodeUnits1 #-}
utf8CodeUnits1 unit1 = Allocator writer 1
where
writer = ArrayWriter $ \array offset ->
TextArray.unsafeWrite array offset unit1
$> succ offset
#else
{-# INLINE utf8CodeUnits1 #-}
utf8CodeUnits1 :: Word8 -> Allocator
utf8CodeUnits1 Word8
unit1 =
Word8 -> Utf16View
Utf16View.utf8CodeUnits1 Word8
unit1 Word16 -> Allocator
utf16CodeUnits1 Word16 -> Word16 -> Allocator
utf16CodeUnits2
#endif
utf8CodeUnits2 :: Word8 -> Word8 -> Allocator
#if MIN_VERSION_text(2,0,0)
{-# INLINEABLE utf8CodeUnits2 #-}
utf8CodeUnits2 unit1 unit2 = Allocator writer 2
where
writer = ArrayWriter $ \array offset -> do
TextArray.unsafeWrite array offset unit1
TextArray.unsafeWrite array (offset + 1) unit2
return $ offset + 2
#else
{-# INLINE utf8CodeUnits2 #-}
utf8CodeUnits2 :: Word8 -> Word8 -> Allocator
utf8CodeUnits2 Word8
unit1 Word8
unit2 =
Word8 -> Word8 -> Utf16View
Utf16View.utf8CodeUnits2 Word8
unit1 Word8
unit2 Word16 -> Allocator
utf16CodeUnits1 Word16 -> Word16 -> Allocator
utf16CodeUnits2
#endif
utf8CodeUnits3 :: Word8 -> Word8 -> Word8 -> Allocator
#if MIN_VERSION_text(2,0,0)
{-# INLINEABLE utf8CodeUnits3 #-}
utf8CodeUnits3 unit1 unit2 unit3 = Allocator writer 3
where
writer = ArrayWriter $ \array offset -> do
TextArray.unsafeWrite array offset unit1
TextArray.unsafeWrite array (offset + 1) unit2
TextArray.unsafeWrite array (offset + 2) unit3
return $ offset + 3
#else
{-# INLINE utf8CodeUnits3 #-}
utf8CodeUnits3 :: Word8 -> Word8 -> Word8 -> Allocator
utf8CodeUnits3 Word8
unit1 Word8
unit2 Word8
unit3 =
Word8 -> Word8 -> Word8 -> Utf16View
Utf16View.utf8CodeUnits3 Word8
unit1 Word8
unit2 Word8
unit3 Word16 -> Allocator
utf16CodeUnits1 Word16 -> Word16 -> Allocator
utf16CodeUnits2
#endif
utf8CodeUnits4 :: Word8 -> Word8 -> Word8 -> Word8 -> Allocator
#if MIN_VERSION_text(2,0,0)
{-# INLINEABLE utf8CodeUnits4 #-}
utf8CodeUnits4 unit1 unit2 unit3 unit4 = Allocator writer 4
where
writer = ArrayWriter $ \array offset -> do
TextArray.unsafeWrite array offset unit1
TextArray.unsafeWrite array (offset + 1) unit2
TextArray.unsafeWrite array (offset + 2) unit3
TextArray.unsafeWrite array (offset + 3) unit4
return $ offset + 4
#else
{-# INLINE utf8CodeUnits4 #-}
utf8CodeUnits4 :: Word8 -> Word8 -> Word8 -> Word8 -> Allocator
utf8CodeUnits4 Word8
unit1 Word8
unit2 Word8
unit3 Word8
unit4 =
Word8 -> Word8 -> Word8 -> Word8 -> Utf16View
Utf16View.utf8CodeUnits4 Word8
unit1 Word8
unit2 Word8
unit3 Word8
unit4 Word16 -> Allocator
utf16CodeUnits1 Word16 -> Word16 -> Allocator
utf16CodeUnits2
#endif
utf16CodeUnits1 :: Word16 -> Allocator
#if MIN_VERSION_text(2,0,0)
{-# INLINE utf16CodeUnits1 #-}
utf16CodeUnits1 = unicodeCodePoint . fromIntegral
#else
{-# INLINEABLE utf16CodeUnits1 #-}
utf16CodeUnits1 :: Word16 -> Allocator
utf16CodeUnits1 Word16
unit =
ArrayWriter -> Int -> Allocator
Allocator ArrayWriter
writer Int
1
where
writer :: ArrayWriter
writer =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
array Int
offset ->
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array Int
offset Word16
unit
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a. Enum a => a -> a
succ Int
offset
#endif
utf16CodeUnits2 :: Word16 -> Word16 -> Allocator
#if MIN_VERSION_text(2,0,0)
{-# INLINE utf16CodeUnits2 #-}
utf16CodeUnits2 unit1 unit2 = unicodeCodePoint cp
where
cp = (((fromIntegral unit1 .&. 0x3FF) `shiftL` 10) .|. (fromIntegral unit2 .&. 0x3FF)) + 0x10000
#else
{-# INLINEABLE utf16CodeUnits2 #-}
utf16CodeUnits2 :: Word16 -> Word16 -> Allocator
utf16CodeUnits2 Word16
unit1 Word16
unit2 =
ArrayWriter -> Int -> Allocator
Allocator ArrayWriter
writer Int
2
where
writer :: ArrayWriter
writer =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
array Int
offset -> do
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array Int
offset Word16
unit1
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array (forall a. Enum a => a -> a
succ Int
offset) Word16
unit2
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int
offset forall a. Num a => a -> a -> a
+ Int
2
#endif
finiteBitsUnsignedBinary :: (FiniteBits a) => a -> Allocator
finiteBitsUnsignedBinary :: forall a. FiniteBits a => a -> Allocator
finiteBitsUnsignedBinary a
val =
ArrayWriter -> Int -> Allocator
Allocator ArrayWriter
writer Int
size
where
writer :: ArrayWriter
writer =
(forall s. MArray s -> Int -> ST s Int) -> ArrayWriter
ArrayWriter forall a b. (a -> b) -> a -> b
$ \MArray s
array Int
arrayStartIndex ->
let go :: a -> Int -> ST s Int
go a
val Int
arrayIndex =
if Int
arrayIndex forall a. Ord a => a -> a -> Bool
>= Int
arrayStartIndex
then do
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array Int
arrayIndex
forall a b. (a -> b) -> a -> b
$ if forall a. Bits a => a -> Int -> Bool
testBit a
val Int
0 then Word16
49 else Word16
48
a -> Int -> ST s Int
go (forall a. Bits a => a -> Int -> a
unsafeShiftR a
val Int
1) (forall a. Enum a => a -> a
pred Int
arrayIndex)
else forall (m :: * -> *) a. Monad m => a -> m a
return Int
indexAfter
indexAfter :: Int
indexAfter =
Int
arrayStartIndex forall a. Num a => a -> a -> a
+ Int
size
in a -> Int -> ST s Int
go a
val (forall a. Enum a => a -> a
pred Int
indexAfter)
size :: Int
size =
forall a. Ord a => a -> a -> a
max Int
1 (forall b. FiniteBits b => b -> Int
finiteBitSize a
val forall a. Num a => a -> a -> a
- forall b. FiniteBits b => b -> Int
countLeadingZeros a
val)
fixedUnsignedDecimal :: (Integral a) => Int -> a -> Allocator
fixedUnsignedDecimal :: forall a. Integral a => Int -> a -> Allocator
fixedUnsignedDecimal Int
size a
val =
Int -> (forall s. MArray s -> Int -> ST s Int) -> Allocator
sizedWriter Int
size forall a b. (a -> b) -> a -> b
$ \MArray s
array Int
startOffset ->
let offsetAfter :: Int
offsetAfter = Int
startOffset forall a. Num a => a -> a -> a
+ Int
size
writeValue :: a -> Int -> ST s Int
writeValue a
val Int
offset =
if Int
offset forall a. Ord a => a -> a -> Bool
>= Int
startOffset
then
if a
val forall a. Eq a => a -> a -> Bool
/= a
0
then case forall a. Integral a => a -> a -> (a, a)
divMod a
val a
10 of
(a
val, a
digit) -> do
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array Int
offset forall a b. (a -> b) -> a -> b
$ Word16
48 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral a
digit
a -> Int -> ST s Int
writeValue a
val (forall a. Enum a => a -> a
pred Int
offset)
else Int -> ST s Int
writePadding Int
offset
else forall (m :: * -> *) a. Monad m => a -> m a
return Int
offsetAfter
writePadding :: Int -> ST s Int
writePadding Int
offset =
if Int
offset forall a. Ord a => a -> a -> Bool
>= Int
startOffset
then do
forall s. MArray s -> Int -> Word16 -> ST s ()
TextArray.unsafeWrite MArray s
array Int
offset Word16
48
Int -> ST s Int
writePadding (forall a. Enum a => a -> a
pred Int
offset)
else forall (m :: * -> *) a. Monad m => a -> m a
return Int
offsetAfter
in a -> Int -> ST s Int
writeValue a
val (forall a. Enum a => a -> a
pred Int
offsetAfter)