Skip to content

Instantly share code, notes, and snippets.

@rblaze
Forked from voidlizard/gist:5194823
Last active December 15, 2015 03:49
Show Gist options
  • Save rblaze/5196790 to your computer and use it in GitHub Desktop.
Save rblaze/5196790 to your computer and use it in GitHub Desktop.
{-# Language BangPatterns #-}
module Main where
import Data.Binary.Get
import Data.Word
import Data.Bits
import Data.List (foldl')
import Test.BenchPress
import Control.Monad
import qualified Data.ByteString.Lazy as BS
csum16 :: BS.ByteString -> Word16
csum16 s = rotate $ trunc $ (foldl' (\acc w -> acc + fromIntegral w) 0) words
where
words = flip runGet s (replicateM (fromIntegral (BS.length s `div` 2)) $ getWord16le)
trunc :: Word32 -> Word16
trunc w = fromIntegral $ complement $ (w .&. 0xFFFF) + (w `shiftR` 16)
rotate :: Word16 -> Word16
rotate x = x `rotateL` 8
{-# INLINE rotate #-}
{-# INLINE csum16 #-}
iter :: [BS.ByteString] -> IO Word16
iter samples = let !s = sum $ take 10000 $ map csum16 $ cycle samples
in return s
main :: IO ()
main = do
let samples = map (BS.replicate 512) [0 .. 255]
print "start"
samples `seq` bench 100 (iter samples)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment