Last active
December 13, 2015 21:18
-
-
Save drchaos/4976205 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE CPP #-} | |
{-# LANGUAGE ScopedTypeVariables , OverloadedStrings #-} | |
module Main where | |
import Criterion.Main | |
import Criterion.Config | |
import qualified Data.ByteString as B | |
import qualified Data.ByteString.Char8 as C | |
import Data.Text as T | |
import Data.Text.Encoding (encodeUtf8) | |
import Codec.Utils | |
#if defined(__GLASGOW_HASKELL__) | |
import GHC.Word | |
import GHC.Base | |
#endif | |
-- | Conversion between 'Word8' and 'Char'. Should compile to a no-op. | |
w2c :: Word8 -> Char | |
#if !defined(__GLASGOW_HASKELL__) | |
w2c = chr . fromIntegral | |
#else | |
w2c = unsafeChr . fromIntegral | |
#endif | |
{-# INLINE w2c #-} | |
-- | Unsafe conversion between 'Char' and 'Word8'. This is a no-op and | |
-- silently truncates to 8 bits Chars > '\255'. It is provided as | |
-- convenience for ByteString construction. | |
c2w :: Char -> Word8 | |
c2w = fromIntegral . fromEnum | |
{-# INLINE c2w #-} | |
----------- String ----------------- | |
bstring :: String -> [Word8] | |
bstring = B.unpack . C.pack | |
mapUnsafe:: String -> [Word8] | |
mapUnsafe = Prelude.map c2w | |
mapSafe:: String -> [Word8] | |
mapSafe = listToOctets . Prelude.map fromEnum | |
dataZ :: String | |
dataZ = Prelude.replicate 100000 'a' | |
---------------- Text ------------------ | |
dataT :: Text | |
dataT = T.replicate 100000 "a" | |
bytestringT :: Text -> [Word8] | |
bytestringT = B.unpack . encodeUtf8 | |
mapT :: Text -> [Word8] | |
mapT xs = Prelude.map c2w (T.unpack xs) | |
mapSafeT:: Text -> [Word8] | |
mapSafeT = mapSafe . T.unpack | |
whnf' :: (a -> [b]) -> a -> Pure | |
whnf' f = whnf (Prelude.foldl const (0::Int) . f) | |
main :: IO () | |
main = defaultMainWith defaultConfig (return ()) [ | |
bgroup "tiny" [ bench "bytestring" $ whnf' bstring dataZ | |
, bench "mapUnsafe" $ whnf' mapUnsafe dataZ | |
, bench "mapSafe" $ whnf' mapSafe dataZ | |
, bench "Text.bytestring" $ whnf' bytestringT dataT | |
, bench "Text.mapUnsafe" $ whnf' mapT dataT | |
, bench "Text.mapSafe" $ whnf' mapSafeT dataT | |
] | |
] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
warming up | |
estimating clock resolution... | |
mean is 1.033241 us (640001 iterations) | |
found 1121893 outliers among 639999 samples (175.3%) | |
492784 (77.0%) low severe | |
629109 (98.3%) high severe | |
estimating cost of a clock call... | |
mean is 24.28554 ns (7 iterations) | |
benchmarking tiny/bytestring | |
mean: 5.397281 ms, lb 5.126731 ms, ub 5.693306 ms, ci 0.950 | |
std dev: 1.451397 ms, lb 1.301517 ms, ub 1.633775 ms, ci 0.950 | |
variance introduced by outliers: 96.797% | |
variance is severely inflated by outliers | |
benchmarking tiny/mapUnsafe | |
mean: 716.6646 us, lb 715.9040 us, ub 718.3144 us, ci 0.950 | |
std dev: 5.470200 us, lb 2.864301 us, ub 9.918355 us, ci 0.950 | |
benchmarking tiny/mapSafe | |
collecting 100 samples, 1 iterations each, in estimated 11.36510 s | |
mean: 104.8577 ms, lb 103.1048 ms, ub 106.6781 ms, ci 0.950 | |
std dev: 9.065831 ms, lb 8.024448 ms, ub 10.29409 ms, ci 0.950 | |
found 3 outliers among 100 samples (3.0%) | |
3 (3.0%) high mild | |
variance introduced by outliers: 73.824% | |
variance is severely inflated by outliers | |
benchmarking tiny/Text.bytestring | |
mean: 2.781987 ms, lb 2.742180 ms, ub 2.823622 ms, ci 0.950 | |
std dev: 207.9665 us, lb 191.8373 us, ub 229.0834 us, ci 0.950 | |
variance introduced by outliers: 67.669% | |
variance is severely inflated by outliers | |
benchmarking tiny/Text.mapUnsafe | |
mean: 1.236949 ms, lb 1.236302 ms, ub 1.237626 ms, ci 0.950 | |
std dev: 3.400257 us, lb 2.979138 us, ub 3.944044 us, ci 0.950 | |
benchmarking tiny/Text.mapSafe | |
collecting 100 samples, 1 iterations each, in estimated 12.57069 s | |
mean: 104.1535 ms, lb 103.2479 ms, ub 105.3710 ms, ci 0.950 | |
std dev: 5.352699 ms, lb 4.177554 ms, ub 7.207393 ms, ci 0.950 | |
found 20 outliers among 100 samples (20.0%) | |
2 (2.0%) low severe | |
2 (2.0%) low mild | |
16 (16.0%) high severe | |
variance introduced by outliers: 49.461% | |
variance is moderately inflated by outliers |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment