Proposal: Remove Num superclass of Bits

On 15 October 2011 00:01, Ian Lynagh
Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits. This would, for example, enable Vectors to get an instance for Bits: http://trac.haskell.org/vector/ticket/59 Discussion period: the usual 2 weeks (29 Oct.) Regards, Bas

On Sat, Oct 15, 2011 at 11:56:27AM +0200, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
Would we just remove default methods like bit i = 1 `shiftL` i x `testBit` i = (x .&. bit i) /= 0 ? Thanks Ian

On Sat, Oct 15, 2011 at 12:11 PM, Ian Lynagh
On Sat, Oct 15, 2011 at 11:56:27AM +0200, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
Would we just remove default methods like bit i = 1 `shiftL` i x `testBit` i = (x .&. bit i) /= 0 ?
You could use DefaultSignatures[1]: class Bits a where default bit :: Num a => Int -> a bit i = 1 `shiftL` i ... Does it have to be/stay portable to non-GHC (or older GHC) compilers? [1] http://www.haskell.org/ghc/docs/7.2.1/html/users_guide/type-class-extensions...
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.

On 15/10/2011, at 11:11, Ian Lynagh wrote:
On Sat, Oct 15, 2011 at 11:56:27AM +0200, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
Would we just remove default methods like bit i = 1 `shiftL` i x `testBit` i = (x .&. bit i) /= 0 ?
The Num superclass is only needed to be able to say 0 and 1. Perhaps we should just add the methods zero and one to Bits? Roman

On Sat, Oct 15, 2011 at 3:56 AM, Roman Leshchinskiy
On 15/10/2011, at 11:11, Ian Lynagh wrote:
On Sat, Oct 15, 2011 at 11:56:27AM +0200, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
Would we just remove default methods like bit i = 1 `shiftL` i x `testBit` i = (x .&. bit i) /= 0 ?
The Num superclass is only needed to be able to say 0 and 1. Perhaps we should just add the methods zero and one to Bits?
That sounds reasonable.

On 15 October 2011 19:23, Johan Tibell
On Sat, Oct 15, 2011 at 3:56 AM, Roman Leshchinskiy
wrote: On 15/10/2011, at 11:11, Ian Lynagh wrote:
On Sat, Oct 15, 2011 at 11:56:27AM +0200, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
Would we just remove default methods like bit i = 1 `shiftL` i x `testBit` i = (x .&. bit i) /= 0 ?
The Num superclass is only needed to be able to say 0 and 1. Perhaps we should just add the methods zero and one to Bits?
That sounds reasonable. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
We can also combine Gábor's and Roman's solutions to get both portability and convenience: zero, one :: a #ifdef __GLASGOW_HASKELL__ default zero, one :: Num a => a zero = 0 one = 1 #endif This way, not existing instances need to be adapted. Another problem is that the default implementation of popCount uses a '-': popCount :: a -> Int popCount = go 0 where go !c 0 = c go c w = go (c+1) (w .&. w - 1) Bas

On Sat, Oct 15, 2011 at 11:00 AM, Bas van Dijk
Another problem is that the default implementation of popCount uses a '-':
popCount :: a -> Int popCount = go 0 where go !c 0 = c go c w = go (c+1) (w .&. w - 1)
I wonder what kind of bitwise algorithms will be hard to implement without using arithmetic. For example, the -1 trick is very common in bit twiddling: http://graphics.stanford.edu/~seander/bithacks.html I guess they can be implemented outside the type class, with an extra num constraint, but then we can't use specialized instructions where available, as in the case of popCount. Or perhaps we can if we use rules to rewrite e.g. popCount :: Word32 -> Int to popCount32# (which turns into a single assembly instruction). -- Johan

On Sat, Oct 15, 2011 at 08:00:21PM +0200, Bas van Dijk wrote:
We can also combine Gábor's and Roman's solutions to get both portability and convenience:
zero, one :: a
#ifdef __GLASGOW_HASKELL__ default zero, one :: Num a => a zero = 0 one = 1 #endif
I think doing this conditionally is a bad idea. Programs will just fail at runtime when using other impls. I also think doing it unconditionally is a bad idea. It significantly raises the barrier to getting another impl to the point where it is useful. Hmm, one can be (bit 0) though. I don't think zero is anything nicer than (clearBit (bit 0) 0). (I don't know what the rules are about using those functions with arguments > bitSize, so I don't know if that would be valid for hypothetical bitSize == 0 instances like ()). Thanks Ian

On 15 October 2011 21:16, Ian Lynagh
On Sat, Oct 15, 2011 at 08:00:21PM +0200, Bas van Dijk wrote:
We can also combine Gábor's and Roman's solutions to get both portability and convenience:
zero, one :: a
#ifdef __GLASGOW_HASKELL__ default zero, one :: Num a => a zero = 0 one = 1 #endif
I think doing this conditionally is a bad idea. Programs will just fail at runtime when using other impls.
I also think doing it unconditionally is a bad idea. It significantly raises the barrier to getting another impl to the point where it is useful.
Hmm, one can be (bit 0) though. But since 'one' would only be used in the default implementation of bit: bit i = one `shiftL` i we would get a circular definition. So we either add a 'one' method to
Agreed, lets drop the default signatures idea. the class or drop the default implementation of bit and so require all instances to define bit themselves. I'm not sure yet which of those two options I like best. However having zero and one as methods almost brings us overloaded booleans. In that regard it would be better to name them false and true though. Ideally we would split Bits into: class Boolean b where false :: b true :: b -- Nice in combination with RebindableSyntax: ifThenElse :: b -> a -> a -> a -- Probably does not have to be a method: not :: b -> b not b = ifThenElse b false true (.&.) :: b -> b -> b x .&. y = ifThenElse x (ifThenElse y true) false (.|.) :: b -> b -> b x .|. y = ifThenElse x true (ifThenElse y true false) The Bits class then becomes: class Boolean b => Bits b where the (.&.), (.|.) are removed because they are defined in Boolean. And ofcourse we would have: instance Boolean Bool where false = False true = True ifThenElse c t e = if c then t else e (.&.) = (&&) (.|.) = (||) And possibly: instance Bits Bool where ... And in the far future we would deprecate (&&) and (||) in favor of (.&.) and (.|.) (or visa versa) and finally remove them. But an important question is: is it wise to treat booleans and bits equally? Because this would allow something like: {-# LANGUAGE RebindableSyntax #-} foo = if 1 then 2 else 3 Regards, Bas

Or even worse, if 3 then True else False would result in 'False' since 3 /= true (1) or 'True' since 3 /= false (0) neither is obvious. Adding just zero and one doesn't completely solve the problem, because testBit uses equality with zero, so an Eq instance is needed. I would just remove the bit and testBit defalut instances, they seem like reasonable primitives to be required for an instance. John

On 16 October 2011 02:41, John Meacham
Or even worse,
if 3 then True else False would result in 'False' since 3 /= true (1) or 'True' since 3 /= false (0)
neither is obvious.
For a C programmer the latter would be obvious. But we're not C programmers...
Adding just zero and one doesn't completely solve the problem, because testBit uses equality with zero, so an Eq instance is needed.
Yes but the Bits class already has Eq as a superclass. This proposal only deals with removing the Num superclass. Bas P.S. Slight correction for my previous message: These would be better definitions of .&. and .|.: x .&. y = ifThenElse x y false x .|. y = ifThenElse x true y since these have the same strictness properties as (&&) and (||).

Hi, Am Samstag, den 15.10.2011, 17:41 -0700 schrieb John Meacham:
I would just remove the bit and testBit defalut instances, they seem like reasonable primitives to be required for an instance.
I agree. Bits is certainly not something that a Haskell Beginner would have to implement every day, but is more likely a task that requires lots of thought and well-written code anyway. Having to implement these two functions as well is not a large burden there. Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

I have to admit this seems to be the most sensible solution, and avoids
stealing names that are more appropriate for numeric instances anyways.
-Edward
On Mon, Oct 17, 2011 at 3:26 AM, Joachim Breitner
Hi,
Am Samstag, den 15.10.2011, 17:41 -0700 schrieb John Meacham:
I would just remove the bit and testBit defalut instances, they seem like reasonable primitives to be required for an instance.
I agree. Bits is certainly not something that a Haskell Beginner would have to implement every day, but is more likely a task that requires lots of thought and well-written code anyway. Having to implement these two functions as well is not a large burden there.
Greetings, Joachim
-- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I agree.
We should then also drop the default implementation of popCount.
What about adding and exporting helper functions like Ian mentioned:
numBit :: (Bits a, Num a) => Int -> a
numBit i = 1 `shiftL` i
{-# INLINE numBit #-}
numPopCount :: (Bits a, Num a) => a -> Int
numPopCount = go 0
where
go !c 0 = c
go c w = go (c+1) (w .&. w - 1)
numTestBit :: (Bits a, Num a) => a -> Int -> Bool
x `numTestBit` i = (x .&. bit i) /= 0
{-# INLINE numTestBit #-}
Not sure about the names though?
On 17 October 2011 19:12, Edward Kmett
I have to admit this seems to be the most sensible solution, and avoids stealing names that are more appropriate for numeric instances anyways. -Edward
On Mon, Oct 17, 2011 at 3:26 AM, Joachim Breitner
wrote: Hi,
Am Samstag, den 15.10.2011, 17:41 -0700 schrieb John Meacham:
I would just remove the bit and testBit defalut instances, they seem like reasonable primitives to be required for an instance.
I agree. Bits is certainly not something that a Haskell Beginner would have to implement every day, but is more likely a task that requires lots of thought and well-written code anyway. Having to implement these two functions as well is not a large burden there.
Greetings, Joachim
-- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/
_______________________________________________ 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 could go with bitDefault popCountDefault, testBitDefault to mirror the
fmapDefault and foldMapDefault in Data.Traversable, but I don't particularly
care which color we paint this bikeshed.
-Edward
On Mon, Oct 17, 2011 at 1:29 PM, Bas van Dijk
I agree.
We should then also drop the default implementation of popCount.
What about adding and exporting helper functions like Ian mentioned:
numBit :: (Bits a, Num a) => Int -> a numBit i = 1 `shiftL` i {-# INLINE numBit #-}
numPopCount :: (Bits a, Num a) => a -> Int numPopCount = go 0 where go !c 0 = c go c w = go (c+1) (w .&. w - 1)
numTestBit :: (Bits a, Num a) => a -> Int -> Bool x `numTestBit` i = (x .&. bit i) /= 0 {-# INLINE numTestBit #-}
Not sure about the names though?
On 17 October 2011 19:12, Edward Kmett
wrote: I have to admit this seems to be the most sensible solution, and avoids stealing names that are more appropriate for numeric instances anyways. -Edward
On Mon, Oct 17, 2011 at 3:26 AM, Joachim Breitner < mail@joachim-breitner.de> wrote:
Hi,
Am Samstag, den 15.10.2011, 17:41 -0700 schrieb John Meacham:
I would just remove the bit and testBit defalut instances, they seem like reasonable primitives to be required for an instance.
I agree. Bits is certainly not something that a Haskell Beginner would have to implement every day, but is more likely a task that requires lots of thought and well-written code anyway. Having to implement these two functions as well is not a large burden there.
Greetings, Joachim
-- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/
_______________________________________________ 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

One other argument against adding "one" and "zero" to the Bits class:
it would be impossible to write code that works with both the old and
new libraries without using something like CPP. The small convenience
when writing class instances doesn't seem worth the loss of backwards
compatibility.
Best,
-Judah
On Mon, Oct 17, 2011 at 10:12 AM, Edward Kmett
I have to admit this seems to be the most sensible solution, and avoids stealing names that are more appropriate for numeric instances anyways. -Edward
On Mon, Oct 17, 2011 at 3:26 AM, Joachim Breitner
wrote: Hi,
Am Samstag, den 15.10.2011, 17:41 -0700 schrieb John Meacham:
I would just remove the bit and testBit defalut instances, they seem like reasonable primitives to be required for an instance.
I agree. Bits is certainly not something that a Haskell Beginner would have to implement every day, but is more likely a task that requires lots of thought and well-written code anyway. Having to implement these two functions as well is not a large burden there.
Greetings, Joachim
-- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/
_______________________________________________ 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 Sunday 16 October 2011, 02:33:58, Bas van Dijk wrote:
However having zero and one as methods almost brings us overloaded booleans. In that regard it would be better to name them false and true though. Ideally we would split Bits into:
class Boolean b where false :: b true :: b
-- Nice in combination with RebindableSyntax: ifThenElse :: b -> a -> a -> a
-- Probably does not have to be a method: not :: b -> b not b = ifThenElse b false true
(.&.) :: b -> b -> b x .&. y = ifThenElse x (ifThenElse y true) false
(.|.) :: b -> b -> b x .|. y = ifThenElse x true (ifThenElse y true false)
The Bits class then becomes:
class Boolean b => Bits b where the (.&.), (.|.) are removed because they are defined in Boolean.
I don't like that. instance Boolean Int where ??? The default methods for (.&.), (.|.) and not would yield quite surprising behaviour. And Int shouldn't be a member of class Boolean anyway.
But an important question is: is it wise to treat booleans and bits equally?
IMO, it isn't.
Because this would allow something like:
{-# LANGUAGE RebindableSyntax #-}
foo = if 1 then 2 else 3
Yech!

On 10/15/11 8:33 PM, Bas van Dijk wrote:
But an important question is: is it wise to treat booleans and bits equally? Because this would allow something like:
{-# LANGUAGE RebindableSyntax #-}
foo = if 1 then 2 else 3
Well, they're both Boolean algebras... But the big question is, or should be, what exactly are we trying to model with the Bits class? The current design is clearly aimed at modelling bitvectors, and just happens to support a few other things too. Given this initial design, it's not at all clear that it would be sensible to replace that with a model for Boolean algebras. Indeed, if I were trying to model Boolean algebras, I'd probably start with some classes for semilattices and then move up to complemented distributive lattices from there. This would set the ground for a better handling of partial orders and repairing the inconsistency of Float/Double's Ord instances. Unfortunately, it's liable to crash into the folks extending Monoid and the like, and it's not entirely clear how best to reconcile their interaction. Personally, I'm -1 for treating Bits like Bool in rebindable syntax. While some Bits instances could sensibly be treated as Booleans in conditionals, not all of them can. In particular, anything other than bivalent Boolean algebras is going to introduce ambiguity. If Bits can be Bools, it should be an opt-in system rather than extending if_then_else_ to incorporate all Boolean algebras in an unclear and ambiguous way. -- Live well, ~wren

I'm with wren -1 on the overloaded boolean stuff, but definitely still +1 on
this proposal over all.
On Sat, Oct 15, 2011 at 9:00 PM, wren ng thornton
On 10/15/11 8:33 PM, Bas van Dijk wrote:
But an important question is: is it wise to treat booleans and bits equally? Because this would allow something like:
{-# LANGUAGE RebindableSyntax #-}
foo = if 1 then 2 else 3
Well, they're both Boolean algebras... But the big question is, or should be, what exactly are we trying to model with the Bits class? The current design is clearly aimed at modelling bitvectors, and just happens to support a few other things too. Given this initial design, it's not at all clear that it would be sensible to replace that with a model for Boolean algebras.
Indeed, if I were trying to model Boolean algebras, I'd probably start with some classes for semilattices and then move up to complemented distributive lattices from there. This would set the ground for a better handling of partial orders and repairing the inconsistency of Float/Double's Ord instances. Unfortunately, it's liable to crash into the folks extending Monoid and the like, and it's not entirely clear how best to reconcile their interaction.
Personally, I'm -1 for treating Bits like Bool in rebindable syntax. While some Bits instances could sensibly be treated as Booleans in conditionals, not all of them can. In particular, anything other than bivalent Boolean algebras is going to introduce ambiguity. If Bits can be Bools, it should be an opt-in system rather than extending if_then_else_ to incorporate all Boolean algebras in an unclear and ambiguous way.
-- Live well, ~wren
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries

On Sun, Oct 16, 2011 at 02:33:58AM +0200, Bas van Dijk wrote:
On 15 October 2011 21:16, Ian Lynagh
wrote: Hmm, one can be (bit 0) though. But since 'one' would only be used in the default implementation of bit: bit i = one `shiftL` i we would get a circular definition.
Doh, good point. So it's true that we could add at least zero (or zeroBits or whatever) to Bits, but whether or not we do, all the existing instances in the wild will need to be altered: either to define zero, or to define bit. If we don't add zero/one, we could define things like numBit :: (Bits a, Num a) => Int -> a numBit i = 1 `shiftL` i to make defining bit and friends slightly easier for existing instances. I also just noticed the isSigned method. That seems a little odd, especially if the Num constraint is removed. Should we remove that method too? Thanks Ian

On 10/16/2011 02:07 PM, Ian Lynagh wrote:
I also just noticed the isSigned method. That seems a little odd, especially if the Num constraint is removed. Should we remove that method too?
It means "does right-shift when the highest bit is 1 put 1-bits or 0-bits in the new high bit positions". The odd name is because this is set up to correspond to signedness (so that right shift is the same as dividing by 2,4,8,etc.,rounding towards negative infinity). -Isaac

On 10/15/2011 06:56 AM, Roman Leshchinskiy wrote:
On 15/10/2011, at 11:11, Ian Lynagh wrote:
On Sat, Oct 15, 2011 at 11:56:27AM +0200, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
Would we just remove default methods like bit i = 1 `shiftL` i x `testBit` i = (x .&. bit i) /= 0 ?
The Num superclass is only needed to be able to say 0 and 1. Perhaps we should just add the methods zero and one to Bits?
As others observed, "one" is only useful for the "bit" method default, and might be meaningless for an "instance () Bits" (whereas the rest of the class makes sense for () as a zero-bit instance, albeit a use doesn't come to mind). Or, similarly to (), a bit-vector which contains its length statically in its type: it would be simpler if length zero was just as valid as any other length. And it would be a bit strange to define 'one' as a value equal to 'zero'. But proposed member 'zero' is plain and simply "all bits zero". I can imagine users of Bits using that method, too. (Side note: are there other classes that want to call things zero? e.g. there is mzero in MonadPlus. Bits is designed to import unqualified easily. Hoogle doesn't find anything currently named 'zero', so it may be fine.) (Horrible side note: 'bit' could default to bit i = one `shiftL` i where one = complement ((complement zero) `shiftL` 1) [/end experienced-C-bit-twiddler confession] ) ~Isaac

On Sun, Oct 16, 2011 at 1:45 AM, Isaac Dupree < ml@isaac.cedarswampstudios.org> wrote:
As others observed, "one" is only useful for the "bit" method default, and might be meaningless for an "instance () Bits" (whereas the rest of the class makes sense for () as a zero-bit instance, albeit a use doesn't come to mind). Or, similarly to (), a bit-vector which contains its length statically in its type: it would be simpler if length zero was just as valid as any other length. And it would be a bit strange to define 'one' as a value equal to 'zero'.
It isn't entirely meaningless it is just out of range. It is perfectly well defined for me to set the 200th bit of a 64 bit integer, it just doesn't do anything. ;) Similarly setting the 1 bit of () would result in (), since there are no bits to set. But proposed member 'zero' is plain and simply "all bits zero". I can imagine users of Bits using that method, too. (Side note: are there other classes that want to call things zero? e.g. there is mzero in MonadPlus. Bits is designed to import unqualified easily. Hoogle doesn't find anything currently named 'zero', so it may be fine.) 'zero' would break quite a few packages of mine, as 'Plus' in semigroupoids uses the name. http://hackage.haskell.org/packages/archive/semigroupoids/1.2.6/doc/html/Dat... It would also break my algebra package, which mixes Bits with algebraic structures. http://hackage.haskell.org/packages/archive/algebra/2.0.2/doc/html/Numeric-A... However, 'algebra' already has to import 90% of what it imports qualified anyways because it doesn't go out of its way to avoid prelude names. =) I'm willing to put in the effort to clean up those packages, and their 20 or so dependents simply because 'zero' does more naturally belong in something either numeric or bit-like, and we're far more likely to make meaningful progress on this front as opposed to progress on a usable numerical tower in my life time.
(Horrible side note: 'bit' could default to
bit i = one `shiftL` i where one = complement ((complement zero) `shiftL` 1) [/end experienced-C-bit-twiddler confession] )
True enough. I would be somewhat concerned that we'd need to make sure it constant folded away to an efficient definition though. -Edward

On 10/16/2011 01:35 PM, Edward Kmett wrote:
On Sun, Oct 16, 2011 at 1:45 AM, Isaac Dupree< ml@isaac.cedarswampstudios.org> wrote:
As others observed, "one" is only useful for the "bit" method default, and might be meaningless for an "instance () Bits" (whereas the rest of the class makes sense for () as a zero-bit instance, albeit a use doesn't come to mind). Or, similarly to (), a bit-vector which contains its length statically in its type: it would be simpler if length zero was just as valid as any other length. And it would be a bit strange to define 'one' as a value equal to 'zero'.
It isn't entirely meaningless it is just out of range. It is perfectly well defined for me to set the 200th bit of a 64 bit integer, it just doesn't do anything. ;) Similarly setting the 1 bit of () would result in (), since there are no bits to set.
Yep. bit 0 === one. I still want to hear counterarguments to "not enough people use 'bit 0' to give it a name". (Also, in the case of numeric Bits, people might call it "1") -Isaac

On Sun, Oct 16, 2011 at 10:35 AM, Edward Kmett
On Sun, Oct 16, 2011 at 1:45 AM, Isaac Dupree < ml@isaac.cedarswampstudios.org> wrote:
As others observed, "one" is only useful for the "bit" method default, and might be meaningless for an "instance () Bits" (whereas the rest of the class makes sense for () as a zero-bit instance, albeit a use doesn't come to mind). Or, similarly to (), a bit-vector which contains its length statically in its type: it would be simpler if length zero was just as valid as any other length. And it would be a bit strange to define 'one' as a value equal to 'zero'.
It isn't entirely meaningless it is just out of range. It is perfectly well defined for me to set the 200th bit of a 64 bit integer, it just doesn't do anything. ;) Similarly setting the 1 bit of () would result in (), since there are no bits to set.
This is hard to implement in practice, as the behavior of assembly instructions for bit manipulation isn't always defined on out of range values and working around that problem in Haskell code will often involve a bad performance trade-off (i.e. adding a branch). We have this problem with shiftL/shiftR, which are terribly slow, leading to no-one using these functions in production quality code (I think I've seen unsafeShiftL/R implemented in at least 3-4 of our most commonly used libraries). I suggest we hurry slowly here. Do we understand what the meaning of the Bits class is? Lets make sure we don't make it harder for use for the majority use case of performing bitwise operations on machine sized quantities. Cheers, Johan

On 15/10/2011, at 10:56, Bas van Dijk wrote:
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
This would, for example, enable Vectors to get an instance for Bits: http://trac.haskell.org/vector/ticket/59
Thinking about this some more, I don't believe that Vectors could be easily made instances of Bits even if the Num superclass is removed. The Bits class assumes that there is exactly one value with no bits set (0), exactly one value with only the nth bit set (bit n), etc. This isn't necessarily true for vectors because they can store different numbers of leading zeroes. So the only sensible Bits instance would have to trim those leading zeroes. That is, length (xs .&. ys) could be anything between 0 and min (length xs) (length ys). I'm not sure how useful such an instance would be. Roman

+1 even with the wrinkles involved.
If this passes (which seems likely to me), I'd also like to propose adding
an instance of Bits to Bool, but we can push that forward separately, I
suppose.
-Edward
On Sat, Oct 15, 2011 at 5:56 AM, Bas van Dijk
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
This would, for example, enable Vectors to get an instance for Bits: http://trac.haskell.org/vector/ticket/59
Discussion period: the usual 2 weeks (29 Oct.)
Regards,
Bas
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 15 October 2011 11:56, Bas van Dijk
On 15 October 2011 00:01, Ian Lynagh
wrote: Removing the Num superclass of Bits was also mentioned, but that would need its own proposal.
Ok, I would like to propose removing the Num superclass of Bits.
This would, for example, enable Vectors to get an instance for Bits: http://trac.haskell.org/vector/ticket/59
Discussion period: the usual 2 weeks (29 Oct.)
Regards,
Bas
The deadline for this proposal has passed. I summarized the discussion and provided a patch for base and ghc in: http://hackage.haskell.org/trac/ghc/ticket/5593 Regards, Bas

I feel this particular question didn't get answered:
I suggest we hurry slowly here. Do we understand what the meaning of the Bits class is? Lets make sure we don't make it harder for use for the majority use case of performing bitwise operations on machine sized quantities.
I don't want to stop the proposal if it has broad support, but have we really thought this thing through? -- Johan

On 29 October 2011 03:53, Johan Tibell
I suggest we hurry slowly here. Do we understand what the meaning of the Bits class is? Lets make sure we don't make it harder for use for the majority use case of performing bitwise operations on machine sized quantities.
The user of the Bits class is only lightly affected. The only change she possibly should make is to add an extra Num constraint to the existing Bits constraint. Bits instances are more affected because they now need to add: bit = ... testBit = ... popCount = ... where they could possibly use the supplied default functions. Do you think these are show-stoppers? Bas

On Sat, Oct 29, 2011 at 9:00 AM, Bas van Dijk
Do you think these are show-stoppers?
No. Do we know which packages would break? I imagine that downloading the hackage tarball and grepping for 'instance Bits' should tell you. Also, does this have any performance impact? -- Johan

On 29 October 2011 18:25, Johan Tibell
No. Do we know which packages would break? I imagine that downloading the hackage tarball and grepping for 'instance Bits' should tell you.
Where can this tarball be downloaded?
Also, does this have any performance impact?
Performance should not be affected. After inlining all instances should use the same definitions. Bas

On Sat, Oct 29, 2011 at 9:41 AM, Bas van Dijk
On 29 October 2011 18:25, Johan Tibell
wrote: No. Do we know which packages would break? I imagine that downloading the hackage tarball and grepping for 'instance Bits' should tell you.
Where can this tarball be downloaded?
http://hackage.haskell.org/packages/hackage.html "archive of just the latest versions of all the packages (230MB tar file)"
Also, does this have any performance impact?
Performance should not be affected. After inlining all instances should use the same definitions.
Good. So none of the current instances use the default* functions? -- Johan

On 29 October 2011 19:22, Johan Tibell
On Sat, Oct 29, 2011 at 9:41 AM, Bas van Dijk
wrote: On 29 October 2011 18:25, Johan Tibell
wrote: No. Do we know which packages would break? I imagine that downloading the hackage tarball and grepping for 'instance Bits' should tell you.
Where can this tarball be downloaded?
http://hackage.haskell.org/packages/hackage.html
"archive of just the latest versions of all the packages (230MB tar file)"
Nice, I will take a look.
Also, does this have any performance impact?
Performance should not be affected. After inlining all instances should use the same definitions.
Good. So none of the current instances use the default* functions?
No, all of them do. But since they previously used the default implementation, which is the same as the default function, the performance should be the same. Bas
participants (14)
-
Bas van Dijk
-
Daniel Fischer
-
Edward Kmett
-
Gábor Lehel
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Ian Lynagh
-
Isaac Dupree
-
Joachim Breitner
-
Johan Tibell
-
John Meacham
-
Judah Jacobson
-
Roman Leshchinskiy
-
wren ng thornton