Proposal: change the Bits instance for Bool to align with other basic types and support branchless calculations

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#)

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

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

Hi all, I am not really convinced that the proposed implementation will be faster -- if the short-circuiting kicks in, I believe it will perform better, even if it uses conditional branching. So unless being convinced by benchmark results, I would prefer the lazier version of these operators. Cheers, Milan
-----Original message----- From: David Feuer
Sent: 27 Sep 2014, 13:59 ... 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

In my quick tests, the branchless form only looked to be about 10% faster.
If others have better benchmarks, I'm happy to defer as my methodology was
rather sloppy.
Considering the alternative is an asymptotic hit, I'm having a hard time
favoring the branchless form as well.
-Edward
On Sun, Sep 28, 2014 at 6:06 AM, Milan Straka
Hi all,
I am not really convinced that the proposed implementation will be faster -- if the short-circuiting kicks in, I believe it will perform better, even if it uses conditional branching.
So unless being convinced by benchmark results, I would prefer the lazier version of these operators.
Cheers, Milan
-----Original message----- From: David Feuer
Sent: 27 Sep 2014, 13:59 ... 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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

10% sounds pretty big to me when you're trying to really squeeze out a bit more performance (which is what tends to lead people to even look at Data.Bits). The asymptotic hit, as you call it, will only hit you if you use what I consider to be the wrong operator. Why would you use .&. and .|. if what you want are && and ||? From the perspective of the Bits concept, Bool is a bitvector that happens to hold only one bit. Why would you expect that to short-circuit? Why would you use it for control flow?

Let's factor your proposal into two pieces, creating branchless boolean
operations and using them in Data.Bits.
I'm 100% on board with adding a combinator for fast non-short-circuiting
boolean and' and or' to Data.Bool.
I'm not yet convinced that the thing in Data.Bits should be that operation
rather than the safer choice.
That turn your argument around on you to some extent. You'd have the fast
branchless version as and' and or' and when you are working monomorphically
with booleans and want short-circuiting behavior you can reach for them. ;)
Why am I being a pain in the ass about this?
I can envision a point in Haskell's future where we might want to let the
combinators in Data.Bits be the ones we use for Bool, where
&&/||/and/or/any/all/not/ just smash things together with Bits and we
generalize more of base.
That would be an incredibly dumb thing to do with non-short-circuiting
versions of the operators.
I for one don't want to cut off that possible future for a 10% gain for a
limited usecase.
I'm not willing to say we should do make that generalization, but I'm also
not willing to cut off that possible future.
-Edward
On Sun, Sep 28, 2014 at 1:15 PM, David Feuer
10% sounds pretty big to me when you're trying to really squeeze out a bit more performance (which is what tends to lead people to even look at Data.Bits). The asymptotic hit, as you call it, will only hit you if you use what I consider to be the wrong operator. Why would you use .&. and .|. if what you want are && and ||? From the perspective of the Bits concept, Bool is a bitvector that happens to hold only one bit. Why would you expect that to short-circuit? Why would you use it for control flow?

On Sun, Sep 28, 2014 at 1:34 PM, Edward Kmett
I can envision a point in Haskell's future where we might want to let the combinators in Data.Bits be the ones we use for Bool, where &&/||/and/or/any/all/not/ just smash things together with Bits and we generalize more of base.
That would be an incredibly dumb thing to do with non-short-circuiting versions of the operators.
I for one don't want to cut off that possible future for a 10% gain for a limited usecase.
My counter-question is: is it even worth considering this generalization if it only makes sense for the Bool case? Because none of the other instances short-circuit. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

That said, you *could* make them short-circuit as well when they are all 0s
or all 1s. I'm not saying we should, as I'm disinclined to introduce even a
cold branch for the check, but it is a possibility.
My main concern is that if (*sigh* probably when) we adopt this proposal we
collapse the whole waveform of possibilities in this space, perhaps
needlessly cutting off future growth directions.
I'm willing to lose the argument here, but I think we should eventually *have
the argument* rather than blindly take the 10%.
I also realize that if we have the argument today, it is probably a sealed
deal, and I'll lose.
Since this proposal is acting as a forcing function, and I don't think I
can stem the tide of opinion on this one I accept the fact that it will
probably go through.
I don't have the time right now to flesh out a full proposal, and I don't
even think it would be a good idea to adopt in the current state of the
Haskell.
If we're talking about a counter-proposal that makes sense in the 7.10 or
likely even 7.12 timeframe, I'm out.
As a fairly weak example:
Many of the other usecases that would be opened up by the alternative to
this proposal are also currently blocked or rendered ugly by the shape of
Bits and are complicated.
e.g. The alternative permits you to use (.&.) and (.|.) in EDSLs when you
need to capture the shape of your conditionals. (As long as you ignore
testBit)
An example of something lost if this proposal is adopted: Folks can't use
(.&.) and (.|.) for freely overridden logical connectives in finally
tagless EDSLs and have Bool just be the default interpreted case.
I can see the appeal of the proposal, it is simple.
I'm personally a weak -1 on the grounds that I think it prematurely forces
us to evaluate the possibilities in this space and takes us in a direction
that cuts us off from paths that could lead to greater generality in the
future.
On a more immediate front, I think the small constant factor performance
gain is counter-balanced by the asymptotic hit, and saying 'don't do that
then' is sweeping an asymptotic issue under the rug.
I also expect that these arguments aren't going to be strong enough to beat
the immediate obviousness of the proposal.
-Edward
On Sun, Sep 28, 2014 at 1:51 PM, Brandon Allbery
On Sun, Sep 28, 2014 at 1:34 PM, Edward Kmett
wrote: I can envision a point in Haskell's future where we might want to let the combinators in Data.Bits be the ones we use for Bool, where &&/||/and/or/any/all/not/ just smash things together with Bits and we generalize more of base.
That would be an incredibly dumb thing to do with non-short-circuiting versions of the operators.
I for one don't want to cut off that possible future for a 10% gain for a limited usecase.
My counter-question is: is it even worth considering this generalization if it only makes sense for the Bool case? Because none of the other instances short-circuit.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I would think what you're trying to do would likely be better with a
different class, by another name, supporting things like .&&., .||., etc.,
or maybe even moving && and || into a class. Another direction is to look
at structures representing other sorts of logics. I just don't see that
Data.Bits is the right place to try to do these things.
On Sep 28, 2014 2:39 PM, "Edward Kmett"
That said, you *could* make them short-circuit as well when they are all 0s or all 1s. I'm not saying we should, as I'm disinclined to introduce even a cold branch for the check, but it is a possibility.
My main concern is that if (*sigh* probably when) we adopt this proposal we collapse the whole waveform of possibilities in this space, perhaps needlessly cutting off future growth directions.
I'm willing to lose the argument here, but I think we should eventually *have the argument* rather than blindly take the 10%.
I also realize that if we have the argument today, it is probably a sealed deal, and I'll lose.
Since this proposal is acting as a forcing function, and I don't think I can stem the tide of opinion on this one I accept the fact that it will probably go through.
I don't have the time right now to flesh out a full proposal, and I don't even think it would be a good idea to adopt in the current state of the Haskell.
If we're talking about a counter-proposal that makes sense in the 7.10 or likely even 7.12 timeframe, I'm out.
As a fairly weak example:
Many of the other usecases that would be opened up by the alternative to this proposal are also currently blocked or rendered ugly by the shape of Bits and are complicated.
e.g. The alternative permits you to use (.&.) and (.|.) in EDSLs when you need to capture the shape of your conditionals. (As long as you ignore testBit)
An example of something lost if this proposal is adopted: Folks can't use (.&.) and (.|.) for freely overridden logical connectives in finally tagless EDSLs and have Bool just be the default interpreted case.
I can see the appeal of the proposal, it is simple.
I'm personally a weak -1 on the grounds that I think it prematurely forces us to evaluate the possibilities in this space and takes us in a direction that cuts us off from paths that could lead to greater generality in the future.
On a more immediate front, I think the small constant factor performance gain is counter-balanced by the asymptotic hit, and saying 'don't do that then' is sweeping an asymptotic issue under the rug.
I also expect that these arguments aren't going to be strong enough to beat the immediate obviousness of the proposal.
-Edward
On Sun, Sep 28, 2014 at 1:51 PM, Brandon Allbery
wrote: On Sun, Sep 28, 2014 at 1:34 PM, Edward Kmett
wrote: I can envision a point in Haskell's future where we might want to let the combinators in Data.Bits be the ones we use for Bool, where &&/||/and/or/any/all/not/ just smash things together with Bits and we generalize more of base.
That would be an incredibly dumb thing to do with non-short-circuiting versions of the operators.
I for one don't want to cut off that possible future for a 10% gain for a limited usecase.
My counter-question is: is it even worth considering this generalization if it only makes sense for the Bool case? Because none of the other instances short-circuit.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Sep 28, 2014 at 2:45 PM, David Feuer
I would think what you're trying to do would likely be better with a different class, by another name, supporting things like .&&., .||., etc., or maybe even moving && and || into a class. Another direction is to look at structures representing other sorts of logics. I just don't see that Data.Bits is the right place to try to do these things.
Yes. This is what I was trying to get at with my question; Data.Bits already has a specific usage, and that usage just doesn't seem to fit the proposed one; that proposal belongs in a related yet different (and, I suspect, significantly different once fleshed out) class. Otherwise, we might well be reinventing the current Enum/Bounded mess or something similar --- trying to wedge something that looks superficially similar into an inappropriate structure. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

That is the approach people are forced to take now. I currently do so in
Ersatz, though I'd intended ever since Bits shed Num to switch to Bits once
we obtained the Bool instance, Lennart does also uses a custom Boolean
class in at least one edsl he has online.
I'm okay if we collectively agree that this is a price we want to pay, I
just want to acknowledge that it there is a price.
You've made it clear you have a very tight vision for the role of Bits. I
personally haven't yet committed to your viewpoint, but I can see the merit
of it. Like I said, I suspect that I've lost this debate.
I feel much better about making a decision if I can see both the upside and
the downside, rather than just listen to the sales pitch, and wanted folks
who were giving it +1s to do so after considering the cost, not just after
considering the small performance benefit.
-Edward
On Sun, Sep 28, 2014 at 2:45 PM, David Feuer
I would think what you're trying to do would likely be better with a different class, by another name, supporting things like .&&., .||., etc., or maybe even moving && and || into a class. Another direction is to look at structures representing other sorts of logics. I just don't see that Data.Bits is the right place to try to do these things. On Sep 28, 2014 2:39 PM, "Edward Kmett"
wrote: That said, you *could* make them short-circuit as well when they are all 0s or all 1s. I'm not saying we should, as I'm disinclined to introduce even a cold branch for the check, but it is a possibility.
My main concern is that if (*sigh* probably when) we adopt this proposal we collapse the whole waveform of possibilities in this space, perhaps needlessly cutting off future growth directions.
I'm willing to lose the argument here, but I think we should eventually *have the argument* rather than blindly take the 10%.
I also realize that if we have the argument today, it is probably a sealed deal, and I'll lose.
Since this proposal is acting as a forcing function, and I don't think I can stem the tide of opinion on this one I accept the fact that it will probably go through.
I don't have the time right now to flesh out a full proposal, and I don't even think it would be a good idea to adopt in the current state of the Haskell.
If we're talking about a counter-proposal that makes sense in the 7.10 or likely even 7.12 timeframe, I'm out.
As a fairly weak example:
Many of the other usecases that would be opened up by the alternative to this proposal are also currently blocked or rendered ugly by the shape of Bits and are complicated.
e.g. The alternative permits you to use (.&.) and (.|.) in EDSLs when you need to capture the shape of your conditionals. (As long as you ignore testBit)
An example of something lost if this proposal is adopted: Folks can't use (.&.) and (.|.) for freely overridden logical connectives in finally tagless EDSLs and have Bool just be the default interpreted case.
I can see the appeal of the proposal, it is simple.
I'm personally a weak -1 on the grounds that I think it prematurely forces us to evaluate the possibilities in this space and takes us in a direction that cuts us off from paths that could lead to greater generality in the future.
On a more immediate front, I think the small constant factor performance gain is counter-balanced by the asymptotic hit, and saying 'don't do that then' is sweeping an asymptotic issue under the rug.
I also expect that these arguments aren't going to be strong enough to beat the immediate obviousness of the proposal.
-Edward
On Sun, Sep 28, 2014 at 1:51 PM, Brandon Allbery
wrote: On Sun, Sep 28, 2014 at 1:34 PM, Edward Kmett
wrote: I can envision a point in Haskell's future where we might want to let the combinators in Data.Bits be the ones we use for Bool, where &&/||/and/or/any/all/not/ just smash things together with Bits and we generalize more of base.
That would be an incredibly dumb thing to do with non-short-circuiting versions of the operators.
I for one don't want to cut off that possible future for a 10% gain for a limited usecase.
My counter-question is: is it even worth considering this generalization if it only makes sense for the Bool case? Because none of the other instances short-circuit.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Sep 28, 2014 at 2:54 PM, Edward Kmett
You've made it clear you have a very tight vision for the role of Bits. I personally haven't yet committed to your viewpoint, but I can see the merit of it. Like I said, I suspect that I've lost this debate.
It might help if (a) we could see some examples of this alternative, and (b) how it interacts with the existing one. And I'm still left wondering how it relates to the non-Bool instances of Bits. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Like I mentioned earlier.
I don't think a fully fleshed out version of the alternative makes sense
today.
Too many small changes would have to go in, and you'd need at least one
factoring of the Bits class to make it compelling.
But since you insist on trying to force me to provide a fully concrete
realization of a counter-proposal, here:
A fully consistent version of it would be to adopt short-circuiting across
all Bits instances (ugh), factor out testBit somehow, then consider
converting
(&&) = (.&.)
(||) = (.|.)
and = getAll . foldMap All
or = Any . foldMap Any
any f = getAny . foldMap (Any . f)
all f = getAll . foldMap (All . f)
not = complement
for a suitably generalized Any and All.
If testBit didn't exist in the class, then you could support (&&) and (||)
for function spaces.
e.g.
isAlnum = isDigit || isAlpha
with no new classes being constructed.
In a world where the current proposal does come to fruition, such a class
would be a separate ad hoc construction, and well, frankly that just would
probably never happen.
Like I said repeatedly above, I believe such a proposal doesn't have a
chance in hell of succeeding today, but the existence of possibilities in
that design space are why I'm hesitant to rush forward here.
-Edward
On Sun, Sep 28, 2014 at 2:56 PM, Brandon Allbery
On Sun, Sep 28, 2014 at 2:54 PM, Edward Kmett
wrote: You've made it clear you have a very tight vision for the role of Bits. I personally haven't yet committed to your viewpoint, but I can see the merit of it. Like I said, I suspect that I've lost this debate.
It might help if (a) we could see some examples of this alternative, and (b) how it interacts with the existing one. And I'm still left wondering how it relates to the non-Bool instances of Bits.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Sep 28, 2014 at 3:14 PM, Edward Kmett
But since you insist on trying to force me to provide a fully concrete realization of a counter-proposal
Well, no. I, and apparently dfeuer, are missing something; I'm trying to figure out what it is. So I don't want a fleshed-out counter-proposal, just pointers to whatever it is that's not at all obvious to us. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Sep 28, 2014 at 3:20 PM, Brandon Allbery
On Sun, Sep 28, 2014 at 3:14 PM, Edward Kmett
wrote: But since you insist on trying to force me to provide a fully concrete realization of a counter-proposal
Well, no. I, and apparently dfeuer, are missing something; I'm trying to figure out what it is. So I don't want a fleshed-out counter-proposal, just pointers to whatever it is that's not at all obvious to us.
Unpacking this a bit more: I fully admit to not being in my element when it comes to things like this. I also have this feeling (which may well be a heuristic that is inappropriate in this case) that, when someone proposes something that sounds like it's specific to a particular instance of a typeclass as belonging in the typeclass itself, something's wrong somewhere. In particular, I'm not quite seeing where this fits within Data.Bits. Now, it may well be that there is some algebra somewhere that makes what I'm seeing a good generalization to all of Data.Bits (and the fact that you're proposing it makes it seem more likely; sadly, it also makes it more likely that it'll soar well over my head...). Flip side, it may be that the use case is compelling enough to justify making the Bool instance "different" from the other Data.Bits instances. Or some other possibility I'm completely missing. Under normal circumstances I'd probably just accept that this is something over my pay grade --- but it seems dfeuer is tripping over the same confusion? So I'm trying to figure out how to get at the part that's not coming together in all of this, that would make it look less like abuse-of-typeclass and more an expression of a mathematical consonance on some level. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Sep 28, 2014 at 3:38 PM, Brandon Allbery
In particular, I'm not quite seeing where this fits within Data.Bits
It just occurred to me that I may have answered part of this myself on IRC yesterday, in a different context: the strictness of the other instances may not indicate a fundamental difference between Bool and the other instances beyond the fact that the other instances are effectively spine-strict bit arrays, whereas Bool is free to *express* laziness. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

You was intended as a collective noun, not an attempt to pick on you in particular. :) Sent from my iPad
On Sep 28, 2014, at 3:20 PM, Brandon Allbery
wrote: On Sun, Sep 28, 2014 at 3:14 PM, Edward Kmett
wrote: But since you insist on trying to force me to provide a fully concrete realization of a counter-proposal Well, no. I, and apparently dfeuer, are missing something; I'm trying to figure out what it is. So I don't want a fleshed-out counter-proposal, just pointers to whatever it is that's not at all obvious to us.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Too many small changes would have to go in, and you'd need at least one factoring of the Bits class to make it compelling. ... A fully consistent version of it would be to adopt short-circuiting across all Bits instances (ugh), factor out testBit somehow, then consider converting If testBit didn't exist in the class ... In a world where the current proposal does come to fruition, such a class would be a separate ad hoc construction, and well, frankly that just would
On Sep 28, 2014 3:14 PM, "Edward Kmett"

On Sun, Sep 28, 2014 at 2:45 PM, David Feuer
I would think what you're trying to do would likely be better with a different class, by another name, supporting things like .&&., .||., etc., or maybe even moving && and || into a class.
So, if I look at this from the angle that the strictness of other Bits instances is an artifact of their being spine-strict bit vectors, I get that the correct answer to this is not a new class but a "strict" newtype on Bool. The standard lazy Bool is by far the more common one, so it's the strict variant that gets the newtype. (Compare the Sum and Product monoid newtype-s.) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Brandon, I think you're articulating a very good point here, in noting that the current set of instances for Bits that *are* *strict* are precisely so because their underlying representations are *spine strict*!
From that perspective, it is definitely valid to argue that the shortcircuiting behavior of bool is in fact correct.
Its also important to keep in mind that theres many examples where the
branchless version of bool is not a win,
and we've not yet articulated an example where someone will be writing code
that is both generic AND branchless (indeed, I'm not certain if there is
actually a meaningful performance win in the fully polymorphic case when
its the desired semantics).
Additionally, one entire space left unaddressed here is this: "why cant we
formulate an optimization algorithm to add to ghc that tries to estimate
when transformation into a (relatively) branchless formulation of the same
code"?
a style i've grown to favor is the following: make it easy to write generic
code thats always correct (wrt complexity), and make it sane to do
specialization/optimization by hand later (and/or teach the compiler.)
I guess my point here is this: while i've many examples of code i've
written that has benefited from being rewritten in a branch free form, that
is because of *bad branch prediction* rather than branching itself.
Branchless code is immune to that problem, but if you dont have bad branch
prediction, the *branching* code will be *faster* */ simpler* than the *branch
free * code.
On Sun, Sep 28, 2014 at 4:03 PM, Brandon Allbery
On Sun, Sep 28, 2014 at 2:45 PM, David Feuer
wrote: I would think what you're trying to do would likely be better with a different class, by another name, supporting things like .&&., .||., etc., or maybe even moving && and || into a class.
So, if I look at this from the angle that the strictness of other Bits instances is an artifact of their being spine-strict bit vectors, I get that the correct answer to this is not a new class but a "strict" newtype on Bool. The standard lazy Bool is by far the more common one, so it's the strict variant that gets the newtype. (Compare the Sum and Product monoid newtype-s.)
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sep 28, 2014 4:15 PM, "Carter Schonwald"
Brandon, I think you're articulating a very good point here, in noting
that the current set of instances for Bits that *are* strict are precisely so because their underlying representations are spine strict!
From that perspective, it is definitely valid to argue that the
shortcircuiting behavior of bool is in fact correct. Maybe, but maybe not so much. For example, it would make sense (to me, at least) to write instance Bits x => Bits [x] where xs .&. ys = zipWith (.&.) xs ys xs .|. ya = zipWith (.|.) xs ys .... This is, I guess you'd say, partially spine-lazy, but it's not short-circuiting.
Its also important to keep in mind that theres many examples where the branchless version of bool is not a win
We've not yet articulated an example where someone will be writing code
Yes, of course. As Edward Kmett indicated, there seems to be clear value in offering both short-circuiting and branchless Bool operators in *some* fashion, whether the branchless ones do or don't end up in Bits. that is both generic AND branchless (indeed, I'm not certain if there is actually a meaningful performance win in the fully polymorphic case when its the desired semantics). If you're arguing that Bool shouldn't be in Bits at all, I could understand that viewpoint. There are a number of Bits members that reduce to useless trivialities for Bool. But I would turn your argument around—where's the code that's both generic and short-circuiting? What makes it valuable to put Bool in Bits at all? The most valuable thing *I* see is to give it branchless operators that match a common interface. Edward Kmett sees a different benefit—but a different benefit requiring the whole class to be refactored to become something else.
Additionally, one entire space left unaddressed here is this: "why cant we formulate an optimization algorithm to add to ghc that tries to estimate when transformation into a (relatively) branchless formulation of the same code"?
This is a *very* good question. I don't know enough about compilation to really say, and there are surely some challenges, but I think it's an important question. If y is already forced, or it's certain to be forced later, then case x of True -> case y of True -> e1 False -> e2 False -> e2 Is the same as if (x & y) then e1 else e2. The next question is whether e1 and e2 are such that the case selection can become a conditional move or something. I have no idea what's involved in general. It also seems more awkward to write if y `seq` x && y then blah else bloop than to write if x .&. y then blah else bloop or even if x `bland` y then blah else bloop --Yucky name, but whatever. But to catch cases programmers might not recognize, I think your idea sounds interesting.
a style i've grown to favor is the following: make it easy to write generic code thats always correct (wrt complexity), and make it sane to do specialization/optimization by hand later (and/or teach the compiler.)
"Correct wrt complexity" is clearly something we disagree on here.
Branchless code is immune to that problem, but if you dont have bad branch prediction, the branching code will be faster / simpler than the branch free code.
Sometimes. The branchless code is sometimes still slightly faster, depending on the situation, and of course it's also *smaller* in many cases.

I'd actually consider that "spine lazy" definition instance Bits x => Bits [x] where xs .&. ys = zipWith (.&.) xs ys xs .|. ya = zipWith (.|.) xs ys to be the proper "short circuiting" definition, because it has the minimal work complexity and just a nice lifted version of the pointwise boolean / bitwise operation. the "is this all True/1s" lifted version doesnt seem to provide a good work complexity bound (seems all or nothing). Otoh, my stance might be a bit heretical or subtley wrong :), NB that I do undersand that unlike the "batch" short circuit, this one would fail if the right hand side was "undefined / error", but thats ok :)

On Sun, Sep 28, 2014 at 2:45 PM, David Feuer
I would think what you're trying to do would likely be better with a different class, by another name, supporting things like .&&., .||., etc., or maybe even moving && and || into a class. Another direction is to look at structures representing other sorts of logics. I just don't see that Data.Bits is the right place to try to do these things.
I agree. The *current* use of (.&.) and (.|.) is for capturing strict bitops and doing so as quickly as possible by trying to map them onto CPU instructions. IMO it makes sense to codify this behavior as part of the intention/goal of the Bits class. I'll gladly take the 10% if I can get it, because that's what bit twiddling is all about. The shortcircuiting behavior of (&&) and (||) is also nice to have on hand, but it's currently restricted to Bool. If we want to generalize this behavior to other types, then it makes sense to introduce a separate class for generalizing these boolean operators. Doing so would (a) allow greater consistency of the Bit instances, and (b) allow other logical operators of a similar shortcircuitable nature without assuming that the shortcircuiting logic ops are at all related to the strict bitvector ops. -- Live well, ~wren

On a more immediate front, I think the small constant factor performance gain is counter-balanced by the asymptotic hit, and saying 'don't do that
On Sep 28, 2014 2:39 PM, "Edward Kmett"

On Sep 28, 2014, at 1:15 PM, David Feuer
wrote: 10% sounds pretty big to me when you're trying to really squeeze out a bit more performance (which is what tends to lead people to even look at Data.Bits). The asymptotic hit, as you call it, will only hit you if you use what I consider to be the wrong operator. Why would you use .&. and .|. if what you want are && and ||? From the perspective of the Bits concept, Bool is a bitvector that happens to hold only one bit. Why would you expect that to short-circuit? Why would you use it for control flow?
This is exactly my thinking, too. I'm +1 for consistency, potential speed in ostensibly straight-line code, and offering the opportunity specifically for this distinct behavior. Anthony

+1 for the same reason, too.
--
Felipe.
Em 28/09/2014 14:35, "Anthony Cowley"
On Sep 28, 2014, at 1:15 PM, David Feuer
wrote: 10% sounds pretty big to me when you're trying to really squeeze out a bit more performance (which is what tends to lead people to even look at Data.Bits). The asymptotic hit, as you call it, will only hit you if you use what I consider to be the wrong operator. Why would you use .&. and .|. if what you want are && and ||? From the perspective of the Bits concept, Bool is a bitvector that happens to hold only one bit. Why would you expect that to short-circuit? Why would you use it for control flow?
This is exactly my thinking, too. I'm +1 for consistency, potential speed in ostensibly straight-line code, and offering the opportunity specifically for this distinct behavior.
Anthony
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi all,
-----Original message----- From: Edward Kmett
Sent: 28 Sep 2014, 13:06 In my quick tests, the branchless form only looked to be about 10% faster.
Maybe we should have a real benchmark. I tried to measure these numbers myself and got very varied results, from no change at all, to 80% faster (that was actually lazy version of && versus strict .&. because of the unboxing). It would be really helpful if someone could create and publish benchmark comparing the implementations (I could not come up with a good one). If we agree on the 10%, I would be -1 on the whole proposal. The reason from the performance view would be that in half of the cases, the shortcutting kicks in and we may get faster execution (and in the worst case 10% slowdown on the ands themselves, not on the rest of the computation). The reason from the language point of view is that I would expect a .&. b to be shortcutting on Bools. Cheers, Milan

Did I miss in this thread an actual use-case for strict and/or for Bool such that it might occur in a tight inner loop? Absent such a use case, I’m -1 on this proposal. If I wanted to use something that I felt had strict bitwise behaviour, I’d never reach for a bool, no matter what operator set I was working with. My instinct would be to reach for a Word8 or the like, since on any real implementation it would take up the same space regardless? Essentially, to my laziness-infected brain, the current instance obeys the principle of least surprise, and the proposed instance violates the sort of wall of “abstraction intuitions” I’ve built up regarding when I should and shouldn’t expect lazy behaviour. -g On September 27, 2014 at 1:59:43 PM, David Feuer (david.feuer@gmail.com) wrote:
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

On Sun, Sep 28, 2014 at 11:06 PM, Gershom B
Did I miss in this thread an actual use-case for strict and/or for Bool such that it might occur in a tight inner loop? Absent such a use case, I’m -1 on this proposal. If I wanted to use something that I felt had strict bitwise behaviour, I’d never reach for a bool, no matter what operator set I was working with. My instinct would be to reach for a Word8 or the like, since on any real implementation it would take up the same space regardless?
Essentially, to my laziness-infected brain, the current instance obeys the principle of least surprise, and the proposed instance violates the sort of wall of “abstraction intuitions” I’ve built up regarding when I should and shouldn’t expect lazy behaviour.
-g
The problem is that Bool is the odd duck with respect to the Data.Bits operations, so the only way your intuition would serve you is if you were sure you would only be working with Bool, in which case the question is why you were reaching for Data.Bits. Anthony
On September 27, 2014 at 1:59:43 PM, David Feuer (david.feuer@gmail.com) wrote:
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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

We currently as a culture tolerate wildly varying strictness in Num's (+),
Applicative's (<*>), Monoid's mappend, etc.
Keep in mind the strictness analyzer isn't going to see through those (or
this) when you are working polymorphically.
Should we require every Monoid's mappend to be strict in both to maybe get
a few percentage points improvement on fold when you have a strict
container?
After all only finitary containers exist, right?
But you *can* foldMap over an infinite list with the subset of Monoids that
are lazy in their right argument. Folks don't seem to have a problem
employing Foldable/Monoid in this scenario in practice, or using foldr to
build a lazy natural when they want to do a lazy list length comparison for
a list that might be infinite.
What distinguishes Bits in this regard?
-Edward
On Mon, Sep 29, 2014 at 10:14 AM, Anthony Cowley
Did I miss in this thread an actual use-case for strict and/or for Bool such that it might occur in a tight inner loop? Absent such a use case, I’m -1 on this proposal. If I wanted to use something that I felt had strict bitwise behaviour, I’d never reach for a bool, no matter what operator set I was working with. My instinct would be to reach for a Word8 or the like, since on any real implementation it would take up the same space regardless?
Essentially, to my laziness-infected brain, the current instance obeys
On Sun, Sep 28, 2014 at 11:06 PM, Gershom B
wrote: the principle of least surprise, and the proposed instance violates the sort of wall of “abstraction intuitions” I’ve built up regarding when I should and shouldn’t expect lazy behaviour. -g
The problem is that Bool is the odd duck with respect to the Data.Bits operations, so the only way your intuition would serve you is if you were sure you would only be working with Bool, in which case the question is why you were reaching for Data.Bits.
Anthony
On September 27, 2014 at 1:59:43 PM, David Feuer (david.feuer@gmail.com)
wrote:
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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sep 29, 2014 10:46 AM, "Edward Kmett"
We currently as a culture tolerate wildly varying strictness in Num's
(+), Applicative's (<*>), Monoid's mappend, etc.
Keep in mind the strictness analyzer isn't going to see through those (or
this) when you are working polymorphically. Do we currently have a convincing case for using *anything* in Bits polymorphically? As far as I can tell, the primary purpose of Bits is to provide a uniform interface to fast bitwise operations on short bitvectors (e.g., Int, Word, etc.) with enough flexibility thrown in to handle things like multi-word bitvectors, and a few other things with varying degrees of grace. Your intuition (which seems generally to be very good) obviously suggests otherwise. I'd be perfectly happy to put this proposal on hold for at least a year to let you figure out what it is that *you* think Bits should be, under two conditions: 1. We add non-short-circuiting and, or, and xor, by some names, somewhere. 2. We explicitly document that the short-circuiting behavior of Bits operations for Bool is as yet completely unspecified and subject to change without notice.
Should we require every Monoid's mappend to be strict in both to maybe get a few percentage points improvement on fold when you have a strict container?
... slippery slope fallacy ...
What distinguishes Bits in this regard?
Its purpose. As it was designed, Bits is *not* for the sort of higher-order generalized fun that you love but rather performance hacks with varying levels of ugliness. I'm 100% in favor of higher-order generalized fun classes being available; I just don't thing Bits is supposed to be one of them. David

On Mon, Sep 29, 2014 at 11:19 AM, David Feuer
On Sep 29, 2014 10:46 AM, "Edward Kmett"
wrote: We currently as a culture tolerate wildly varying strictness in Num's
(+), Applicative's (<*>), Monoid's mappend, etc.
Keep in mind the strictness analyzer isn't going to see through those
(or this) when you are working polymorphically.
Do we currently have a convincing case for using *anything* in Bits polymorphically? As far as I can tell, the primary purpose of Bits is to provide a uniform interface to fast bitwise operations on short bitvectors (e.g., Int, Word, etc.) with enough flexibility thrown in to handle things like multi-word bitvectors, and a few other things with varying degrees of grace. Your intuition (which seems generally to be very good) obviously suggests otherwise. I'd be perfectly happy to put this proposal on hold for at least a year to let you figure out what it is that *you* think Bits should be, under two conditions:
1. We add non-short-circuiting and, or, and xor, by some names, somewhere. 2. We explicitly document that the short-circuiting behavior of Bits operations for Bool is as yet completely unspecified and subject to change without notice.
I'd go for that.
Should we require every Monoid's mappend to be strict in both to maybe get a few percentage points improvement on fold when you have a strict container?
... slippery slope fallacy ...
Touché.
What distinguishes Bits in this regard?
Its purpose. As it was designed, Bits is *not* for the sort of higher-order generalized fun that you love but rather performance hacks with varying levels of ugliness. I'm 100% in favor of higher-order generalized fun classes being available; I just don't thing Bits is supposed to be one of them.
But if it is only intended for ad hoc overloading at known concrete instances then the uniformity argument doesn't hold. It is really for the higher order "generalized fun" use case that your argument is strongest. ;) -Edward

On Mon, Sep 29, 2014 at 11:19 AM, David Feuer
Do we currently have a convincing case for using *anything* in Bits polymorphically? As far as I can tell, the primary purpose of Bits is to provide a uniform interface to fast bitwise operations on short bitvectors (e.g., Int, Word, etc.) with enough flexibility thrown in to handle things like multi-word bitvectors, and a few other things with varying degrees of grace. Your intuition (which seems generally to be very good) obviously suggests otherwise. I'd be perfectly happy to put this proposal on hold for at least a year to let you figure out what it is that *you* think Bits should be, under two conditions:
1. We add non-short-circuiting and, or, and xor, by some names, somewhere. 2. We explicitly document that the short-circuiting behavior of Bits operations for Bool is as yet completely unspecified and subject to change without notice.
I don't think that bits is designed to "provide a uniform interface to fast bitwise operations on short bitvectors". It is designed to provide uniform operations over datatypes that can be treated as a sequence of bits. In general, it seems to do this just fine. All operations we define in our core libraries, should, by default, have two properties: 1) They are efficient, 2) They are maximally defined; i.e. they produce bottom as infrequently as possible. The latter property, in general, should constrain the former. This proposal is to make a default implementation violate my expectations by asking, in the name of _sometimes_ efficiency, that it be less general than it can be, and produce nonterminating results when _otherwise_ it might terminate. I don't think either condition is necessary. If somebody wants "extra strict" operations on bool, they can define those in an external package. I don't feel it is a common enough use case to go into base. Furthermore, I don't see explicitly documenting that something is subject to change when it may well be that its fine and there's no reason to change it. I can think of three uses for the Bool instance for bits. First, because `xor` may be a more clear name than (/=) for a use of Bool. Second, to test a generic operation on Bits in a minimal context as a "sanity check". Third, because I may wish to write _logical operations_ in a manner polymorphic over my "bool-like" type. In the first two cases, the existing behaviour is fine. In the last case, it is a net positive. In the continued absence of any good arguments for why we _should_ make this change, at this point I'm a firm -1. -g

On Sep 29, 2014, at 12:21 PM, Gershom B
wrote: On Mon, Sep 29, 2014 at 11:19 AM, David Feuer
wrote: Do we currently have a convincing case for using *anything* in Bits polymorphically? As far as I can tell, the primary purpose of Bits is to provide a uniform interface to fast bitwise operations on short bitvectors (e.g., Int, Word, etc.) with enough flexibility thrown in to handle things like multi-word bitvectors, and a few other things with varying degrees of grace. Your intuition (which seems generally to be very good) obviously suggests otherwise. I'd be perfectly happy to put this proposal on hold for at least a year to let you figure out what it is that *you* think Bits should be, under two conditions:
1. We add non-short-circuiting and, or, and xor, by some names, somewhere. 2. We explicitly document that the short-circuiting behavior of Bits operations for Bool is as yet completely unspecified and subject to change without notice.
I don't think that bits is designed to "provide a uniform interface to fast bitwise operations on short bitvectors". It is designed to provide uniform operations over datatypes that can be treated as a sequence of bits. In general, it seems to do this just fine. All operations we define in our core libraries, should, by default, have two properties: 1) They are efficient, 2) They are maximally defined; i.e. they produce bottom as infrequently as possible. The latter property, in general, should constrain the former. This proposal is to make a default implementation violate my expectations by asking, in the name of _sometimes_ efficiency, that it be less general than it can be, and produce nonterminating results when _otherwise_ it might terminate.
Are you then proposing that we make the other Bits instances lazier? Your argument is well-stated, and this discussion is quite interesting, so I really don't mean that question rhetorically. We clearly could test an individual CInt before applying a binary operation, and I support the notion of adding such an operation somewhere. But I wouldn't support removing the current behavior, which is why I then come down on Bool differently than you. Anthony
I don't think either condition is necessary. If somebody wants "extra strict" operations on bool, they can define those in an external package. I don't feel it is a common enough use case to go into base. Furthermore, I don't see explicitly documenting that something is subject to change when it may well be that its fine and there's no reason to change it.
I can think of three uses for the Bool instance for bits. First, because `xor` may be a more clear name than (/=) for a use of Bool. Second, to test a generic operation on Bits in a minimal context as a "sanity check". Third, because I may wish to write _logical operations_ in a manner polymorphic over my "bool-like" type. In the first two cases, the existing behaviour is fine. In the last case, it is a net positive.
In the continued absence of any good arguments for why we _should_ make this change, at this point I'm a firm -1.
-g

On Mon, Sep 29, 2014 at 12:21 PM, Gershom B
I can think of three uses for the Bool instance for bits. First, because `xor` may be a more clear name than (/=) for a use of Bool. Second, to test a generic operation on Bits in a minimal context as a "sanity check". Third, because I may wish to write _logical operations_ in a manner polymorphic over my "bool-like" type. In the first two cases, the existing behaviour is fine. In the last case, it is a net positive.
I agree about the desire to abstract over lattices so we can write logic programs over generalized truth values. However, this is not what the Bits class gives us. Most of the operations explicitly assume we're working with bitvectors. Some of these operations (bit, setBit, clearBit,...) can be argued to make sense for any complete Boolean algebra, but doing so requires an arbitrary mapping between atoms and Int. Other operations (shift, rotate,...) don't make sense with arbitrary Int--atom mappings because they rely on an ordering of atoms (as given by the ordering of Int). Moreover, being intuitionists, if we were to codify lattices as a type class then we'd surely want to have a class for Heyting algebras, and then have Boolean algebras as a subclass. -- Live well, ~wren

Part of what distinguishes Bits here is specifically what we're discussing. There is some level of agreement that there should be a non-short-circuiting operation on Bool somewhere, and the proposal points out that such a thing fits into Bits quite well because it is consistent with other Bits instances. It happens that this also suits my intuition about the use of bitwise operations, and that turning to Bits suggests that the programmer is digging a bit deeper into a representation than is perhaps usual. Since different folks have different intuitions, however, I think a vote is the only useful way forward. To be clear, I very much like the idea of having generalized and- (and or-)like operations that are short-circuiting, and appreciate that the dearth of operator symbols is a nuisance (my EDSLs are indeed littered with various and'-ish corruptions). But it is not apparent to me that the right solution should involve a redesign of Bits as you've sketched. This is hard, though: while I sympathize with you not wanting to moot your future proposal yet, this veers rather close to a kind of individual veto power that I'm not sure is fair. I don't think there is any specific rush for the original proposal, so would it be possible to try to tackle both of these issues in the near future so that we might aim for a better holistic solution? Anthony
On Sep 29, 2014, at 10:46 AM, Edward Kmett
wrote: We currently as a culture tolerate wildly varying strictness in Num's (+), Applicative's (<*>), Monoid's mappend, etc.
Keep in mind the strictness analyzer isn't going to see through those (or this) when you are working polymorphically.
Should we require every Monoid's mappend to be strict in both to maybe get a few percentage points improvement on fold when you have a strict container?
After all only finitary containers exist, right?
But you can foldMap over an infinite list with the subset of Monoids that are lazy in their right argument. Folks don't seem to have a problem employing Foldable/Monoid in this scenario in practice, or using foldr to build a lazy natural when they want to do a lazy list length comparison for a list that might be infinite.
What distinguishes Bits in this regard?
-Edward
On Mon, Sep 29, 2014 at 10:14 AM, Anthony Cowley
wrote: On Sun, Sep 28, 2014 at 11:06 PM, Gershom B wrote: Did I miss in this thread an actual use-case for strict and/or for Bool such that it might occur in a tight inner loop? Absent such a use case, I’m -1 on this proposal. If I wanted to use something that I felt had strict bitwise behaviour, I’d never reach for a bool, no matter what operator set I was working with. My instinct would be to reach for a Word8 or the like, since on any real implementation it would take up the same space regardless?
Essentially, to my laziness-infected brain, the current instance obeys the principle of least surprise, and the proposed instance violates the sort of wall of “abstraction intuitions” I’ve built up regarding when I should and shouldn’t expect lazy behaviour.
-g
The problem is that Bool is the odd duck with respect to the Data.Bits operations, so the only way your intuition would serve you is if you were sure you would only be working with Bool, in which case the question is why you were reaching for Data.Bits.
Anthony
On September 27, 2014 at 1:59:43 PM, David Feuer (david.feuer@gmail.com) wrote:
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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, Sep 29, 2014 at 12:32 PM, Anthony Cowley
Part of what distinguishes Bits here is specifically what we're discussing. There is some level of agreement that there should be a non-short-circuiting operation on Bool somewhere, and the proposal points out that such a thing fits into Bits quite well because it is consistent with other Bits instances. It happens that this also suits my intuition about the use of bitwise operations, and that turning to Bits suggests that the programmer is digging a bit deeper into a representation than is perhaps usual. Since different folks have different intuitions, however, I think a vote is the only useful way forward.
Maybe I should just formally propose newtype Bit = Bit { unBit :: Bool } with the appropriate derived instances, and a strict Bits instance. The distinction between Bit and Bool also seems to fit my intuitions. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sep 29, 2014, at 12:39 PM, Brandon Allbery
wrote: On Mon, Sep 29, 2014 at 12:32 PM, Anthony Cowley
wrote: Part of what distinguishes Bits here is specifically what we're discussing. There is some level of agreement that there should be a non-short-circuiting operation on Bool somewhere, and the proposal points out that such a thing fits into Bits quite well because it is consistent with other Bits instances. It happens that this also suits my intuition about the use of bitwise operations, and that turning to Bits suggests that the programmer is digging a bit deeper into a representation than is perhaps usual. Since different folks have different intuitions, however, I think a vote is the only useful way forward. Maybe I should just formally propose
newtype Bit = Bit { unBit :: Bool }
with the appropriate derived instances, and a strict Bits instance. The distinction between Bit and Bool also seems to fit my intuitions.
Yes, the differing opinions make the newtype introduction appealing, but if Bits is eventually made lazier to support generalized short-circuiting, will this then be a wart there? I've really liked a lot of the points I've seen from both sides of this debate, so it'd be great to navigate the branchy vs branchless crossroads with a bit of style. Anthony
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Mon, Sep 29, 2014 at 12:50 PM, Anthony Cowley
Yes, the differing opinions make the newtype introduction appealing, but if Bits is eventually made lazier to support generalized short-circuiting, will this then be a wart there? I've really liked a lot of the points I've seen from both sides of this debate, so it'd be great to navigate the branchy vs branchless crossroads with a bit of style.
I think the point is that this exactly addresses that: people who want the spine strictness of the existing Bits instances get it for Bool via the newtype and corresponding strict Bits instance (and maybe other instances), people who want laziness get it via Bool --- and this also advances the cause of generalizing existing Bool-related things, since the next obvious thing to do is make it possible to use && and || on a typeclass instead of hardcoded for Bool, so they can be extended to Bit. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I don't think this newtype idea is likely to work out so beautifully.
The main problem is that real code is likely to do a lot of mixing and
matching of short-circuit and non-short-circuit code. The newtype
concept requires a lot of wrapping and unwrapping to express that, and
trying out different approaches to find the fastest leads to a lot of
complicated wrapper rearrangement.
On Mon, Sep 29, 2014 at 12:54 PM, Brandon Allbery
On Mon, Sep 29, 2014 at 12:50 PM, Anthony Cowley
wrote: Yes, the differing opinions make the newtype introduction appealing, but if Bits is eventually made lazier to support generalized short-circuiting, will this then be a wart there? I've really liked a lot of the points I've seen from both sides of this debate, so it'd be great to navigate the branchy vs branchless crossroads with a bit of style.
I think the point is that this exactly addresses that: people who want the spine strictness of the existing Bits instances get it for Bool via the newtype and corresponding strict Bits instance (and maybe other instances), people who want laziness get it via Bool --- and this also advances the cause of generalizing existing Bool-related things, since the next obvious thing to do is make it possible to use && and || on a typeclass instead of hardcoded for Bool, so they can be extended to Bit.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (9)
-
Anthony Cowley
-
Brandon Allbery
-
Carter Schonwald
-
David Feuer
-
Edward Kmett
-
Felipe Almeida Lessa
-
Gershom B
-
Milan Straka
-
wren romano