
Hi, Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal? Thanks, Maurício

Hi
Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
No, though it is an interesting idea.
You can get pretty close with existing Haskell though: (bin 100010011) where bin :: Integer -> Integer, and is left as an exercise for the reader. Obviously its not as high performance, as proper binary literals, but if you write them as top-level constants, they'll only be computed once and shouldn't end up being in the performance critical bits. Thanks Neil

ndmitchell:
Hi
Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
No, though it is an interesting idea.
You can get pretty close with existing Haskell though:
(bin 100010011)
where bin :: Integer -> Integer, and is left as an exercise for the reader. Obviously its not as high performance, as proper binary literals, but if you write them as top-level constants, they'll only be computed once and shouldn't end up being in the performance critical bits.
And the call to `bin' be lifted into the Num class I suspect... leading to raw binary literals, using overloaded literal syntax. So I guess we do have binary literals then. -- Don

On 10/24/07, Neil Mitchell
Hi
Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
No, though it is an interesting idea.
You can get pretty close with existing Haskell though:
(bin 100010011)
where bin :: Integer -> Integer, and is left as an exercise for the reader. Obviously its not as high performance, as proper binary literals, but if you write them as top-level constants, they'll only be computed once and shouldn't end up being in the performance critical bits.
To make it efficient you could use Template Haskell and have the bin function generate the constant which could then be spliced in. I suppose it would look something like: $(bin 100010011) Not too bad. /Josef

On Thu, Oct 25, 2007 at 02:40:36PM +0200, Josef Svenningsson wrote:
On 10/24/07, Neil Mitchell
wrote: Hi
Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
No, though it is an interesting idea.
You can get pretty close with existing Haskell though:
(bin 100010011)
where bin :: Integer -> Integer, and is left as an exercise for the reader. Obviously its not as high performance, as proper binary literals, but if you write them as top-level constants, they'll only be computed once and shouldn't end up being in the performance critical bits.
To make it efficient you could use Template Haskell and have the bin function generate the constant which could then be spliced in. I suppose it would look something like: $(bin 100010011)
Eek. Template Haskell is massive overkill for this, and requires that every syntax author muddle with syntax trees. The Right Way to handle this is constant folding of user defined functions; although I'm not sure what form such a mechanism would take. Perhaps a pragma FOLD 1 saying that this function should always be inlined if the first argument is ground? Lack of general constant folding is a serious problem with GHC. Much overly-slow numerics code is due to x^2, which loops over the bitwise structure of 2 each time. If (^) was marked FOLD 2, then we would get (after a small amount of the compiler's usual symbolic manipulations) x * x. Bitwise operations are not folded even if both arguments are ground. This would require a few primitive rules for xorInt# and friends, but you'd also need something like FOLD to bypass the checks in shiftR etc. Perhaps some kind of termination analysis (well founded recursion on presburger arithmetic could certainly handle (^) and bin, no clue how hard something like that is to implement) is in order. I see an alarming trend towards ad-hoc transformation patterns and excessive use of syntactic abstraction, when we should just be using Haskell's rich semantic structure. Total functions, full laziness, and compile time evaluation of finite non-bottom CAFs... Stefan

On Thu, 25 Oct 2007, Stefan O'Rear wrote:
On Thu, Oct 25, 2007 at 02:40:36PM +0200, Josef Svenningsson wrote:
On 10/24/07, Neil Mitchell
wrote: You can get pretty close with existing Haskell though:
(bin 100010011)
where bin :: Integer -> Integer, and is left as an exercise for the reader. Obviously its not as high performance, as proper binary literals, but if you write them as top-level constants, they'll only be computed once and shouldn't end up being in the performance critical bits.
To make it efficient you could use Template Haskell and have the bin function generate the constant which could then be spliced in. I suppose it would look something like: $(bin 100010011)
Eek. Template Haskell is massive overkill for this, and requires that every syntax author muddle with syntax trees. The Right Way to handle this is constant folding of user defined functions; although I'm not sure what form such a mechanism would take. Perhaps a pragma FOLD 1 saying that this function should always be inlined if the first argument is ground?
Generally I prefer to solve such problems within Haskell instead of blowing up the language. If at all number literals are supported, then that should be done in a consistent manner. E.g. in Modula-3 you write 2_10000, 8_20, 16_10, for a binary, octal, hexadecimal number. http://www.cs.tut.fi/lintula/manual/modula3/m3defn/html/numbers.html I can't remember that I ever used this feature, because Modula-3 has much better support for bit oriented data, namely bit sets. In Haskell we could achieve the same with an appropriate library. (bin "11002000") would not yield a compile time error, but due to its seldom usage this might be ok. I vote for this approach.
Lack of general constant folding is a serious problem with GHC. Much overly-slow numerics code is due to x^2, which loops over the bitwise structure of 2 each time. If (^) was marked FOLD 2, then we would get (after a small amount of the compiler's usual symbolic manipulations) x * x.
I hoped GHC did this all the time. :-(
I see an alarming trend towards ad-hoc transformation patterns and excessive use of syntactic abstraction, when we should just be using Haskell's rich semantic structure.
Agreed!
Total functions, full laziness, and compile time evaluation of finite non-bottom CAFs...
If I write a program that approximates a big but fixed number of digits of Pi - how can we prevent the compiler from computing Pi, and generating a program which contains just the digits of Pi as constant data?

On Thu, Oct 25, 2007 at 09:41:27PM +0200, Henning Thielemann wrote:
Total functions, full laziness, and compile time evaluation of finite non-bottom CAFs...
If I write a program that approximates a big but fixed number of digits of Pi - how can we prevent the compiler from computing Pi, and generating a program which contains just the digits of Pi as constant data?
-O0 Stefan

On Thu, 25 Oct 2007, Stefan O'Rear wrote:
On Thu, Oct 25, 2007 at 09:41:27PM +0200, Henning Thielemann wrote:
Total functions, full laziness, and compile time evaluation of finite non-bottom CAFs...
If I write a program that approximates a big but fixed number of digits of Pi - how can we prevent the compiler from computing Pi, and generating a program which contains just the digits of Pi as constant data?
-O0
The compiled program should run fast nevertheless ...

Don Stewart
Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
No, though it is an interesting idea.
Presumably it is less common since octal and hexadecimal are more compact and almost as easy to interpret as bit patterns? Why would you want them? Prelude> let bin = foldl... Prelude> 0o232 154 Prelude> bin [0,1,0, 0,1,1, 0,1,0] 154 Prelude> 0xD29A 53914 Prelude> bin [1,1,0,1, 0,0,1,0, 1,0,0,1, 1,0,1,0] 53914 -k -- If I haven't seen further, it is by standing in the footprints of giants

Hello all, // PLS, no flame I think the question was not whether there's a way, how to handle the problem of encryption of a binary number to anything suitable and, more or less, readable by a human and transforming it to a binary form, but whether there's such a literal or not and whether it is bad idea to have something like 0b10111011. From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters. Moreover, allowing ADA features for all numeric literals we could have 0b1011_1011 ;-) where the type would be Num a => a, of course. So, i would expect only two answers: NO, it is ......., or YES, in version 6.9.0 it is possible. ;-) Dusan Ketil Malde wrote:
Don Stewart
writes: Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
No, though it is an interesting idea.
Presumably it is less common since octal and hexadecimal are more compact and almost as easy to interpret as bit patterns? Why would you want them?
Prelude> let bin = foldl... Prelude> 0o232 154 Prelude> bin [0,1,0, 0,1,1, 0,1,0] 154 Prelude> 0xD29A 53914 Prelude> bin [1,1,0,1, 0,0,1,0, 1,0,0,1, 1,0,1,0] 53914
-k
-- Dusan Kolar tel: +420 54 114 1238 UIFS FIT VUT Brno fax: +420 54 114 1270 Bozetechova 2 e-mail: kolar@fit.vutbr.cz Brno 612 66 Czech Republic --

Dusan Kolar
// PLS, no flame
I apologize if my post came across as such, that was certainly not the intent.
I think the question was [..] whether there's such a literal or not and whether it is bad idea to have something like 0b10111011.
I agree.
From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.
And from my point of view, 0xEE or 0x273 are equally readable, and even more succinct. If you are into bit-twiddling, that is. For user-friendly bitfields you should obviously provide a higher level interface.
So, i would expect only two answers: NO, it is ......., or YES, in version 6.9.0 it is possible. ;-)
As far as I know, there are no such plans. Send in a patch and see if it gets accepted :-) -k -- If I haven't seen further, it is by standing in the footprints of giants

Hi,
We have no binary literals in Haskell and there are situations when it
would have been useful to have this feature (e.g., if the spec of
something that you are working with is already provided using this
notation).
While it may be useful to have overloaded binary literals in the usual
Haskell style, during my PhD work I found that it is also useful
(perhaps even more so) to add non-overloaded binary literals where the
number of digits in the literal determines its type. The notation
that I used was B00010011 to be a literal of type Word8. I chose this
notation over one like 0b00010011 because I think that the leading
zero is confusing (the literal usually has plenty of 0s already!).
Also, I like it that my notation suggests that the literals are the
constructors of the corresponding word type.
I think that binary literals are more useful when you work with fairly
short bit sequences, mixing and matching to make longer ones.
Unfortunately, in current Haskell we don't have a family of word types
but instead, a few predefined ones, the shortest of which is Word8, so
perhaps this notation is not so useful. (I have encoded families of
word types in Haskell, but I think that having language support for
such things as in my work on bitdata, in bluespec, or cryptol is much
nicer).
Hope this helps!
-Iavor
On 10/25/07, Ketil Malde
Dusan Kolar
writes: // PLS, no flame
I apologize if my post came across as such, that was certainly not the intent.
I think the question was [..] whether there's such a literal or not and whether it is bad idea to have something like 0b10111011.
I agree.
From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.
And from my point of view, 0xEE or 0x273 are equally readable, and even more succinct. If you are into bit-twiddling, that is. For user-friendly bitfields you should obviously provide a higher level interface.
So, i would expect only two answers: NO, it is ......., or YES, in version 6.9.0 it is possible. ;-)
As far as I know, there are no such plans. Send in a patch and see if it gets accepted :-)
-k -- If I haven't seen further, it is by standing in the footprints of giants _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.
how about using ghc's new overloaded strings for this? "10111011"::Binary there used to be a way to link to ghc head's docs, but i can't find it right now. the test is http://darcs.haskell.org/testsuite/tests/ghc-regress/typecheck/should_compil... and the xml docs would be http://darcs.haskell.org/ghc/docs/users_guide/glasgow_exts.xml claus

claus.reinke:
From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.
how about using ghc's new overloaded strings for this?
"10111011"::Binary
there used to be a way to link to ghc head's docs, but i can't find it right now. the test is
http://darcs.haskell.org/testsuite/tests/ghc-regress/typecheck/should_compil...
and the xml docs would be
http://darcs.haskell.org/ghc/docs/users_guide/glasgow_exts.xml
Why not use a Num instance for Binary, with fromInteger :: Integer -> a, Yielding, 10111011 :: Binary Overloaded numeric literals seem better here than strings :) -- Don

dons:
claus.reinke:
From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.
how about using ghc's new overloaded strings for this?
"10111011"::Binary
there used to be a way to link to ghc head's docs, but i can't find it right now. the test is
http://darcs.haskell.org/testsuite/tests/ghc-regress/typecheck/should_compil...
and the xml docs would be
http://darcs.haskell.org/ghc/docs/users_guide/glasgow_exts.xml
Why not use a Num instance for Binary, with fromInteger :: Integer -> a, Yielding,
10111011 :: Binary
Overloaded numeric literals seem better here than strings :)
Something like this: import Data.List import Data.Bits newtype Binary = Binary Integer deriving (Eq, Show) instance Num Binary where fromInteger n = Binary . roll . map (read.return) . show $ n where roll = foldl' unstep 0 unstep a 1 = a `shiftL` 1 .|. fromIntegral 1 unstep a 0 = a `shiftL` 1 unstep a _ = error "Invalid character in binary literal" Yielding, *A> 0 :: Binary Binary 0 *A> 101 :: Binary Binary 5 *A> 1111 :: Binary Binary 15 *A> 1010101011010111 :: Binary Binary 43735 *A> 42 :: Binary Binary *** Exception: Invalid character in binary literal

On Thu, Oct 25, 2007 at 09:52:27AM -0700, Don Stewart wrote:
dons:
claus.reinke:
From my point of view, the difference between 0b10111011 and (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.
how about using ghc's new overloaded strings for this?
"10111011"::Binary
there used to be a way to link to ghc head's docs, but i can't find it right now. the test is
http://darcs.haskell.org/testsuite/tests/ghc-regress/typecheck/should_compil...
and the xml docs would be
http://darcs.haskell.org/ghc/docs/users_guide/glasgow_exts.xml
Why not use a Num instance for Binary, with fromInteger :: Integer -> a, Yielding,
10111011 :: Binary
Overloaded numeric literals seem better here than strings :)
Something like this:
import Data.List import Data.Bits
newtype Binary = Binary Integer deriving (Eq, Show)
instance Num Binary where fromInteger n = Binary . roll . map (read.return) . show $ n where roll = foldl' unstep 0
unstep a 1 = a `shiftL` 1 .|. fromIntegral 1 unstep a 0 = a `shiftL` 1 unstep a _ = error "Invalid character in binary literal"
Yielding,
*A> 0 :: Binary Binary 0
*A> 101 :: Binary Binary 5
*A> 1111 :: Binary Binary 15
*A> 1010101011010111 :: Binary Binary 43735
*A> 42 :: Binary Binary *** Exception: Invalid character in binary literal
This would have some decidedly weird consequences fromIntegral (6::Int) :: Binary Binary *** Exception: Invalid character in binary literal and that constant 6 can be somewhere far removed from the actual binary cast. also, fromInteger (toInteger x + toInteger y ) :: Binary /= x + y all sorts of oddness will result. John -- John Meacham - ⑆repetae.net⑆john⑈

On Thu, 25 Oct 2007, Don Stewart wrote:
claus.reinke:
how about using ghc's new overloaded strings for this?
"10111011"::Binary
there used to be a way to link to ghc head's docs, but i can't find it right now. the test is
http://darcs.haskell.org/testsuite/tests/ghc-regress/typecheck/should_compil...
and the xml docs would be
http://darcs.haskell.org/ghc/docs/users_guide/glasgow_exts.xml
Why not use a Num instance for Binary, with fromInteger :: Integer -> a, Yielding,
10111011 :: Binary
Overloaded numeric literals seem better here than strings :)
The result would be very unexpected - it reminds me much on C's octal interpretation of all number literals starting with a 0.

On Thu, Oct 25, 2007 at 04:06:56PM +0200, Dusan Kolar wrote:
Hello all,
// PLS, no flame
I think the question was not whether there's a way, how to handle the problem of encryption of a binary number to anything suitable and, more or less, readable by a human and transforming it to a binary form, but whether there's such a literal or not and whether it is bad idea to have something like 0b10111011.
I have often wanted this feature too. I think the only complaint someone might have is that 'b' is also a valid hexadecimal character, which can be confusing if the number is out of context. John -- John Meacham - ⑆repetae.net⑆john⑈

Prelude> read "0o232" :: Int 154 Prelude> read "0xD29A" :: Int 53914 Prelude> Maurício wrote:
Hi,
Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal?
Thanks, Maurício
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (12)
-
Claus Reinke
-
Dan Weston
-
Don Stewart
-
Dusan Kolar
-
Henning Thielemann
-
Iavor Diatchki
-
John Meacham
-
Josef Svenningsson
-
Ketil Malde
-
Maurício
-
Neil Mitchell
-
Stefan O'Rear