Skip to content

Instantly share code, notes, and snippets.

@snoyberg
Created April 11, 2012 04:39
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 snoyberg/2356925 to your computer and use it in GitHub Desktop.
Save snoyberg/2356925 to your computer and use it in GitHub Desktop.
Get the hex representation of a ByteString
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as S8
import Data.Bits
import System.Environment (getArgs)
import qualified Numeric
import Test.QuickCheck (quickCheck)
import Test.QuickCheck.Arbitrary (Arbitrary (..))
import Criterion.Main
main :: IO ()
main = do
args <- getArgs
case args of
["test"] -> test
[] -> bench'
_ -> error "Usage: hex [test]"
test :: IO ()
test = quickCheck $ \bs -> simple bs == unfoldrN_MS1 bs
instance Arbitrary S.ByteString where
arbitrary = fmap S.pack arbitrary
bench' :: IO ()
bench' = defaultMain
[ bench "simple" $ whnf simple sample
, bench "unfoldrN_MS1" $ whnf unfoldrN_MS1 sample
]
where
sample = S.replicate 5000 29
simple :: S.ByteString -> S.ByteString
simple =
S.concatMap $ \c -> S8.pack $ pad $ Numeric.showHex c []
where
pad [x] = ['0', x]
pad s = s
unfoldrN_MS1 :: S.ByteString -> S.ByteString
unfoldrN_MS1 bs0 =
fst $ S.unfoldrN (S.length bs0 * 2) go (Left bs0)
where
go (Left bs) =
case S.uncons bs of
Nothing -> Nothing
Just (w, bs') ->
let w1 = w `shiftR` 4
w2 = w .&. 15
c1 = toC w1
c2 = toC w2
in Just (c1, Right (c2, bs'))
go (Right (c, bs)) = Just (c, Left bs)
toC w
| w < 10 = w + 48
| otherwise = w + 87
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment