
On Thu, Sep 20, 2012 at 11:57 PM, Bas van Dijk
On 20 September 2012 22:55, Gregory Collins
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:
That's what I originally expected the results to be. The fact that removing
those INLINE pragmas makes things better is........strange. I'm going to
forward this thread to Simon to see what he thinks about it.
G
--
Gregory Collins