Skip to content

Instantly share code, notes, and snippets.

@zoranbosnjak
Created November 29, 2023 11:20
Show Gist options
  • Save zoranbosnjak/7887d843056f07bac6061d20970e1d6a to your computer and use it in GitHub Desktop.
Save zoranbosnjak/7887d843056f07bac6061d20970e1d6a to your computer and use it in GitHub Desktop.
ByteString and Builder test
{-# LANGUAGE NumericUnderscores #-}
import Test.Tasty.Bench
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as Bsl
import qualified Data.ByteString.Builder as Bld
import qualified Data.List
import Data.Word
import Asterix.Bytes as Bytes
benchInspect :: Benchmark
benchInspect = bgroup "Inspect test"
[ bench "using ByteString" $ nf (usingByteString 0) sample
, bench "using Bytes" $ nf (usingBytes 0) (Bytes.fromByteString sample)
]
where
sample :: ByteString
sample = BS.pack $ replicate 10_000_000 0
usingByteString :: Word8 -> ByteString -> Word8
usingByteString !acc s
| BS.null s = acc
| otherwise = usingByteString (acc + BS.head s) (BS.tail s)
usingBytes :: Word8 -> Bytes -> Word8
usingBytes !acc s
| Bytes.null s = acc
| otherwise = usingBytes (acc + Bytes.head s) (Bytes.tail s)
benchConstruct :: Benchmark
benchConstruct = bgroup "Construct test"
[ bench "using Builder" $ nf usingBuilder sample
, bench "using Bytes" $ nf usingBytes sample
, bench "naive" $ nf naive sample
]
where
sample :: [Word8]
sample = replicate 1_000_000 0
usingBuilder :: [Word8] -> [ByteString]
usingBuilder = Bsl.toChunks . Bld.toLazyByteString . mconcat . fmap Bld.word8
usingBytes :: [Word8] -> [ByteString]
usingBytes = Bytes.toChunks . mconcat . fmap Bytes.singleton
naive :: [Word8] -> [ByteString]
naive = Data.List.singleton . mconcat . fmap BS.singleton
main :: IO ()
main = defaultMain
[ benchInspect
, benchConstruct
]
-- | ByteString and ByteString.Builder combined
module Asterix.Bytes where
import Prelude hiding (length)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as Bsl
import qualified Data.ByteString.Builder as Bld
import Data.ByteString (ByteString)
import Data.ByteString.Builder (Builder)
import Data.Word
import Data.String
data Bytes = Bytes
{ toByteString :: ByteString
, toBuilder :: Builder
, length :: Int
}
instance IsString Bytes where
fromString = fromByteString . fromString
instance Semigroup Bytes where
b1 <> b2 = Bytes
{ toByteString = toByteString b1 <> toByteString b2
, toBuilder = toBuilder b1 <> toBuilder b2
, length = length b1 + length b2
}
instance Monoid Bytes where
mempty = empty
instance Eq Bytes where
b1 == b2
= (length b1 == length b2) -- check length first for performance
&& (toByteString b1 == toByteString b2)
instance Ord Bytes where
compare b1 b2 = compare (toByteString b1) (toByteString b2)
instance Show Bytes where
show = show . toByteString
empty :: Bytes
empty = Bytes
{ toByteString = mempty
, toBuilder = mempty
, length = 0
}
singleton :: Word8 -> Bytes
singleton val = Bytes
{ toByteString = BS.singleton val
, toBuilder = Bld.word8 val
, length = 1
}
fromByteString :: ByteString -> Bytes
fromByteString bs = Bytes
{ toByteString = bs
, toBuilder = Bld.byteString bs
, length = BS.length bs
}
head :: Bytes -> Word8
head = BS.head . toByteString
last :: Bytes -> Word8
last = BS.last . toByteString
tail :: Bytes -> Bytes
tail = fromByteString . BS.tail . toByteString
init :: Bytes -> Bytes
init = fromByteString . BS.init . toByteString
null :: Bytes -> Bool
null = (<= 0) . length
take :: Int -> Bytes -> Bytes
take n s = fromByteString $ BS.drop n $ toByteString s
drop :: Int -> Bytes -> Bytes
drop n s = fromByteString $ BS.take n $ toByteString s
splitAt :: Int -> Bytes -> (Bytes, Bytes)
splitAt n s =
let (a, b) = BS.splitAt n (toByteString s)
in (fromByteString a, fromByteString b)
toChunks :: Bytes -> [ByteString]
toChunks = Bsl.toChunks . Bld.toLazyByteString . toBuilder
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment