Skip to content

Instantly share code, notes, and snippets.

@mpickering
Created February 8, 2023 10:20
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save mpickering/eb2d127b9eeb9153b44e3815a4181d17 to your computer and use it in GitHub Desktop.
Save mpickering/eb2d127b9eeb9153b44e3815a4181d17 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -dumpdir dumps/9.4 #-}
#if MIN_VERSION_GLASGOW_HASKELL(9,5,0,0)
{-# OPTIONS_GHC -dumpdir dumps/9.6 #-}
#endif
{-# OPTIONS_GHC -ddump-simpl -ddump-verbose-inlinings -ddump-to-file -dsuppress-all -ddump-stg-final #-}
module BenchShort (benchShort) where
import Control.DeepSeq (force)
import Data.Foldable (foldMap)
import Data.Maybe (listToMaybe)
import Data.Monoid
import Data.String
import Test.Tasty.Bench
import Prelude hiding (words, head, tail)
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString.Short as S
import Data.ByteString.Builder
import Data.ByteString.Builder.Extra (byteStringCopy,
byteStringInsert,
intHost)
import Data.ByteString.Builder.Internal (ensureFree)
import Data.ByteString.Builder.Prim (BoundedPrim, FixedPrim,
(>$<))
import qualified Data.ByteString.Builder.Prim as P
import qualified Data.ByteString.Builder.Prim.Internal as PI
import Foreign
import System.Random
import Control.DeepSeq
--import FindIndex
------------------------------------------------------------------------------
-- Benchmark
------------------------------------------------------------------------------
-- benchmark wrappers
---------------------
--
-- Helpers
-------------
find_index s = S.findIndex (== nl) s
-- ASCII \n to ensure no typos
nl :: Word8
nl = 0xa
{-# INLINE nl #-}
-- non-inlined equality test
nilEq :: Word8 -> Word8 -> Bool
{-# NOINLINE nilEq #-}
nilEq = (==)
-- lines of 200 letters from a to e, followed by repeated letter f
absurdlong :: S.ShortByteString
absurdlong = S.replicate 200 0x61 <> S.singleton nl
<> S.replicate 200 0x62 <> S.singleton nl
<> S.replicate 200 0x63 <> S.singleton nl
<> S.replicate 200 0x64 <> S.singleton nl
<> S.replicate 200 0x65 <> S.singleton nl
<> S.replicate 999999 0x66
-- benchmarks
-------------
benchShort :: Benchmark
benchShort = bgroup "ShortByteString"
[ bgroup "ShortByteString strict first index" $ [ bench "FindIndices" $ nf (listToMaybe . S.findIndices (== nl)) absurdlong
, bench "FindIndex" $ nf (S.findIndex (== nl)) absurdlong
, bench "ElemIndex" $ nf (S.elemIndex nl) absurdlong
]
, bgroup "ShortByteString index equality inlining" $
[ bench "FindIndices/inlined" $ nf (S.findIndices (== nl)) absurdlong
, bench "FindIndices/non-inlined" $ nf (S.findIndices (nilEq nl)) absurdlong
, bench "FindIndex/inlined" $ nf find_index absurdlong
, bench "FindIndex/non-inlined" $ nf (S.findIndex (nilEq nl)) absurdlong
]
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment