[web-devel] Data.Word8 (word8 library)
Bas van Dijk
v.dijk.bas at gmail.com
Thu Sep 20 23:57:07 CEST 2012
On 20 September 2012 22:55, Gregory Collins <greg at gregorycollins.net> wrote:
> consequently, there seems to be no reason to use the word8 library: not only
> is it not faster, it's actually a pessimization.
When I run the following benchmark:
main :: IO ()
main = do
input <- S.readFile "bench.hs"
defaultMain
[ bench "Word8-local" $ nf (S.length . S.map toLower8) input
, bench "Char8 toLowerC" $ nf (S.length . S8.map toLowerC) input
]
toLower8 :: Word8 -> Word8
toLower8 w
| isUpper8 w = w + 32
| otherwise = w
{-# INLINE toLower8 #-}
isUpper8 :: Word8 -> Bool
isUpper8 w = 0x41 <= w && w <= 0x5a
|| 0xc0 <= w && w <= 0xd6
|| 0xd8 <= w && w <= 0xde
{-# INLINE isUpper8 #-}
toLowerC :: Char -> Char
toLowerC w
| isUpperC w = unsafeChr $ ord w + 0x20
| otherwise = w
isUpperC :: Char -> Bool
isUpperC w = '\x41' <= w && w <= '\x5a'
|| '\xc0' <= w && w <= '\xd6'
|| '\xd8' <= w && w <= '\xde'
I get the following results:
benchmarking Word8-local
mean: 8.939985 us, lb 8.921876 us, ub 8.960350 us, ci 0.950
std dev: 97.99953 ns, lb 86.79926 ns, ub 113.6396 ns, ci 0.950
benchmarking Char8 toLowerC
mean: 3.468023 us, lb 3.461577 us, ub 3.475718 us, ci 0.950
std dev: 35.93801 ns, lb 30.56892 ns, ub 49.77021 ns, ci 0.950
However when I _remove_ the INLINE pragmas they become equally fast:
benchmarking Word8-local
mean: 3.563220 us, lb 3.555527 us, ub 3.572971 us, ci 0.950
std dev: 44.12678 ns, lb 36.22663 ns, ub 58.41914 ns, ci 0.950
benchmarking Char8 toLowerC
mean: 3.534374 us, lb 3.526955 us, ub 3.542637 us, ci 0.950
std dev: 40.27805 ns, lb 35.64414 ns, ub 46.59990 ns, ci 0.950
Adding an INLINE pragma to toLowerC and isUpperC doesn't change the results.
I'm on GHC-7.6.1 using -O2.
Bas
More information about the web-devel
mailing list