{-# LANGUAGE UnliftedFFITypes #-}
module Jsonifier.Size
where
import Jsonifier.Prelude
import qualified Data.Text.Internal as Text
import qualified Data.Text.Array as TextArray
import qualified Jsonifier.Ffi as Ffi
{-# INLINE object #-}
object :: Int -> Int -> Int
object :: Int -> Int -> Int
object Int
rowsAmount Int
contentsSize =
Int
forall p. Num p => p
curlies Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
commas Int
rowsAmount Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
colonsAndQuotes Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
contentsSize
where
curlies :: p
curlies =
p
2
colonsAndQuotes :: Int
colonsAndQuotes =
Int
rowsAmount Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
3
{-# INLINE array #-}
array :: Int -> Int -> Int
array :: Int -> Int -> Int
array Int
elementsAmount Int
contentsSize =
Int
forall p. Num p => p
brackets Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
commas Int
elementsAmount Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
contentsSize
where
brackets :: p
brackets =
p
2
{-# INLINE commas #-}
commas :: Int -> Int
commas :: Int -> Int
commas Int
rowsAmount =
if Int
rowsAmount Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1
then Int
0
else Int -> Int
forall a. Enum a => a -> a
pred Int
rowsAmount
stringBody :: Text -> Int
stringBody :: Text -> Int
stringBody (Text.Text Array
arr Int
off Int
len) =
ByteArray# -> CSize -> CSize -> IO CInt
Ffi.countStringAllocationSize
(Array -> ByteArray#
TextArray.aBA Array
arr) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
IO CInt -> (IO CInt -> CInt) -> CInt
forall a b. a -> (a -> b) -> b
& IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO
CInt -> (CInt -> Int) -> Int
forall a b. a -> (a -> b) -> b
& CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral