
I don't have benchmarks, but I will. My intuition on this is that Data.Bits
is about *arithmetic*, not control flow. I *usually* expect arithmetic to
be strict. I also *usually* expect to do arithmetic in contexts where
branch prediction is likely to be crummy. I further *usually* expect a
compiler to optimize arithmetic on little things very aggressively, without
regard for the sorts of ordering constraints that short-circuiting imposes.
Do we have a benchmark of the relative performance of the short-circuiting
vs. non-short-circuiting versions?
There *is* a consistency argument in that we don't currently try to
short-circuit any of the other instances, but increasing strictness means
reduced termination, so we should look before we leap.
On the other hand there is also a cultural bias towards being as lazy as
possible, and we derive a lot of benefit in terms of reasoning across the
entire ecosystem from the uniformity of that bias.
If we are going to consider trading asymptotics for constant factors, we
should at least take a look at if we're getting anything for our trade.
-Edward
On Sat, Sep 27, 2014 at 1:59 PM, David Feuer
Currently, the (.&.) and (.|.) methods for Bool are short-circuiting, defined like this:
instance Bits Bool where (.&.) = (&&)
(.|.) = (||)
Unlike the instances for Int, Word, etc., this gives short-circuiting behavior (conditionally lazy in the second operand). Unfortunately, this requires a conditional branch to implement, which can sometimes be bad. Since (&&) and (||) are readily available to anyone who wants short-circuiting, I propose that we use the following instead. Note that the Bits class does not specify anything about this aspect of instance behavior.
x .&. y = tagToEnum# (dataToTag# x `andI#` dataToTag# y)
x .|. y = tagToEnum# (dataToTag# x `orI#` dataToTag# y)
The rest of the operations look like this:
x `xor` y = tagToEnum# (dataToTag# x `xorI#` dataToTag# y)
complement x = tagToEnum# (dataToTag# x `xorI#` 1#)
shift x s = testBit x s
rotate x _ = x
-- I don't think we gain anything changing this one. bit 0 = True bit _ = False
testBit x b = tagToEnum# (dataToTag# x `andI#` (dataToTag# b ==# 0#))
bitSizeMaybe _ = Just 1
bitSize _ = 1
isSigned _ = False
popCount x = I# (dataToTag# x)
instance FiniteBits Bool where finiteBitSize _ = 1 countTrailingZeros x = I# (dataToTag# x `xorI#` 1#) countLeadingZeros x = I# (dataToTag# x `xorI#` 1#)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries