
If you're bored... can you come up with a solution to this? http://warp.povusers.org/ProgrammingChallenge.html (Obviously a pretty silly challenge, but hey.) My first instinct was to use Data.Bits - but I see no instance for Double. (Presumably because performing bitwise operations on a Double is a pretty odd thing to want to do.) So my next guess is to do some bizzare type system hackery that allows you to transform a Double into... whichever integer type is the same size, and proceed from there. Does anybody know how to do that? (Otherwise... wasn't there some library somewhere for serialising values in binary?)

On 31/05/07, Andrew Coppin
If you're bored... can you come up with a solution to this?
Try using floatToDigits: http://haskell.org/ghc/docs/latest/html/libraries/base/Numeric.html#v%3Afloa... "floatToDigits takes a base and a non-negative RealFloat number, and returns a list of digits and an exponent." -- -David House, dmhouse@gmail.com

"David House"
On 31/05/07, Andrew Coppin
wrote: If you're bored... can you come up with a solution to this?
Try using floatToDigits: http://haskell.org/ghc/docs/latest/html/libraries/base/Numeric.html#v%3Afloa...
"floatToDigits takes a base and a non-negative RealFloat number, and returns a list of digits and an exponent."
I think you also need floatRadix and floatDigits. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Jon Fairbairn wrote:
"David House"
writes: On 31/05/07, Andrew Coppin
wrote: If you're bored... can you come up with a solution to this?
Try using floatToDigits: http://haskell.org/ghc/docs/latest/html/libraries/base/Numeric.html#v%3Afloa...
"floatToDigits takes a base and a non-negative RealFloat number, and returns a list of digits and an exponent."
I think you also need floatRadix and floatDigits.
Note that the challenge asks for the "internal" bitmap representation of an IEEE double-precision integer - not the mathematical binary expansion. (In particular, things like Infinity and NaN have special bit sequences.) Did I mention that this is a silly challange yet?

Andrew Coppin
Jon Fairbairn wrote:
"David House"
writes: On 31/05/07, Andrew Coppin
wrote: If you're bored... can you come up with a solution to this?
Try using floatToDigits: http://haskell.org/ghc/docs/latest/html/libraries/base/Numeric.html#v%3Afloa...
"floatToDigits takes a base and a non-negative RealFloat number, and returns a list of digits and an exponent."
I think you also need floatRadix and floatDigits.
Note that the challenge asks for the "internal" bitmap representation of an IEEE double-precision integer - not the mathematical binary expansion.
Hence my remark above.
(In particular, things like Infinity and NaN have special bit sequences.)
Did I mention that this is a silly challange yet?
Yes, but you didn't say that it's not only silly but demonstrates the opposite of expressiveness as it's all about breaking an abstraction and must be non-portable code (because it's definition is that it won't give the same results on different hardware), so such code should be *hard* to write in a good language. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2007-05-07)

On 31 May 2007 21:52:33 +0100, Jon Fairbairn
Yes, but you didn't say that it's not only silly but demonstrates the opposite of expressiveness as it's all about breaking an abstraction and must be non-portable code (because it's definition is that it won't give the same results on different hardware), so such code should be *hard* to write in a good language.
Well, I would suggest that maybe *good* is not completely congruent with *expressive* (at least for this case). If I want to write a program to learn how IEEE floats are constructed, by destructing them, then I *should* be able to. I have no solutions of my own though :-( I wait in eager expectation.... D.

"Dougal Stanton"
On 31 May 2007 21:52:33 +0100, Jon Fairbairn
wrote: Yes, but you didn't say that it's not only silly but demonstrates the opposite of expressiveness as it's all about breaking an abstraction and must be non-portable code (because it's definition is that it won't give the same results on different hardware), so such code should be *hard* to write in a good language.
Well, I would suggest that maybe *good* is not completely congruent with *expressive* (at least for this case). If I want to write a program to learn how IEEE floats are constructed, by destructing them, then I *should* be able to.
You can. Getting a notion of how they are constructed (independent of the precise hardware) is easy, (just try foo x = floatToDigits (floatRadix x) x foo (1/0) together with looking at floatDigits etc), getting the precise machine representation is harder (but possible). But then, if you want to do that, why shouldn't you use some assembler? It would be even more instructive, after all.
I have no solutions of my own though :-( I wait in eager expectation....
Isn't the combination of the functions mentioned earlier in the thread enough for you to do it? (even disregarding unsafeCoerce). -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On 31/05/07, Andrew Coppin
Note that the challenge asks for the "internal" bitmap representation of an IEEE double-precision integer - not the mathematical binary expansion. (In particular, things like Infinity and NaN have special bit sequences.)
Ah, sorry, then disregard my solution. I did wonder why you'd immediately jump to Data.Bits. -- -David House, dmhouse@gmail.com

Andrew Coppin wrote:
Note that the challenge asks for the "internal" bitmap representation of an IEEE double-precision integer
Actually it didn't. It asked for the machine's internal representation of a double precision float, and you are not guaranteed that this representation conforms to IEEE 7-whatsit. It is beyond me what you're going to do with that unspecified representation, though.
Did I mention that this is a silly challange yet?
Silly, yes. Challenge, no. We can do the same the C++ guy did, it's only a question if we need to. Something close to this: | import Foreign.Marshal | import Foreign.Ptr | import Data.Word | | valueToBytes :: Storable a => a -> IO [Word8] | valueToBytes a = with a $ \p -> peekBytes (castPtr b) (sizeOf a) Reversing the list and hammering it down to single bits is trivial after that. -Udo -- Structure is _nothing_ if it is all you got. Skeletons _spook_ people if they try to walk around on their own. I really wonder why XML does not. -- Erik Naggum

The site seems to be asking for the internal floating point representation. So it doesn't matter if it's IEEE 754, if the ints are 2-complements, or whatever. I used this code as a quick hack for one of my programs, but I think it would work in this case. It should work for any Storable type. import qualified Data.ByteString as BS import Data.ByteString.Base import Foreign.ForeignPtr import Foreign.Storable binPut num = do fptr <- mallocForeignPtrBytes (sizeOf num) withForeignPtr (castForeignPtr fptr) (\x -> poke x num) BS.writeFile "/tmp/foo" (BS.reverse $ fromForeignPtr fptr (sizeOf num))

On 6/3/07, Rafael Almeida
The site seems to be asking for the internal floating point representation. So it doesn't matter if it's IEEE 754, if the ints are 2-complements, or whatever. I used this code as a quick hack for one of my programs, but I think it would work in this case. It should work for any Storable type.
import qualified Data.ByteString as BS import Data.ByteString.Base import Foreign.ForeignPtr import Foreign.Storable binPut num = do fptr <- mallocForeignPtrBytes (sizeOf num) withForeignPtr (castForeignPtr fptr) (\x -> poke x num) BS.writeFile "/tmp/foo" (BS.reverse $ fromForeignPtr fptr (sizeOf num))
Ops, that reverse was needed for what I was doing, but not needed for this particular problem, so the code should actually be: import qualified Data.ByteString as BS import Data.ByteString.Base import Foreign.ForeignPtr import Foreign.Storable binPut num = do fptr <- mallocForeignPtrBytes (sizeOf num) withForeignPtr (castForeignPtr fptr) (\x -> poke x num) BS.writeFile "/tmp/foo" (fromForeignPtr fptr (sizeOf num))

almeidaraf:
On 6/3/07, Rafael Almeida
wrote: The site seems to be asking for the internal floating point representation. So it doesn't matter if it's IEEE 754, if the ints are 2-complements, or whatever. I used this code as a quick hack for one of my programs, but I think it would work in this case. It should work for any Storable type.
import qualified Data.ByteString as BS import Data.ByteString.Base import Foreign.ForeignPtr import Foreign.Storable binPut num = do fptr <- mallocForeignPtrBytes (sizeOf num) withForeignPtr (castForeignPtr fptr) (\x -> poke x num) BS.writeFile "/tmp/foo" (BS.reverse $ fromForeignPtr fptr (sizeOf num))
Ops, that reverse was needed for what I was doing, but not needed for this particular problem, so the code should actually be:
import qualified Data.ByteString as BS import Data.ByteString.Base import Foreign.ForeignPtr import Foreign.Storable binPut num = do fptr <- mallocForeignPtrBytes (sizeOf num) withForeignPtr (castForeignPtr fptr) (\x -> poke x num) BS.writeFile "/tmp/foo" (fromForeignPtr fptr (sizeOf num)) ^^^ Interesting use of ByteStrings to print foreigin ptr arrays there.
-- Don

On Thu, May 31, 2007 at 08:47:28PM +0100, Andrew Coppin wrote:
If you're bored... can you come up with a solution to this?
http://warp.povusers.org/ProgrammingChallenge.html
(Obviously a pretty silly challenge, but hey.)
I fail to see what this has to do with "expressive power", which it's supposed to test. In this test assembler is the most expressive language. Yes, silly. Best regards Tomek

Tomasz Zielonka wrote:
On Thu, May 31, 2007 at 08:47:28PM +0100, Andrew Coppin wrote:
If you're bored... can you come up with a solution to this?
http://warp.povusers.org/ProgrammingChallenge.html
(Obviously a pretty silly challenge, but hey.)
I fail to see what this has to do with "expressive power", which it's supposed to test. In this test assembler is the most expressive language. Yes, silly.
Silly? Yes. Proposed by a C++ programmer? Yes. (Personally I can't think of a reason for *wanting* to do such a thing... but never mind. I am however mildly - I emphasize mildly - curiose to see if it can be done in Haskell.)

On Thursday 31 May 2007, Andrew Coppin wrote:
If you're bored... can you come up with a solution to this?
http://warp.povusers.org/ProgrammingChallenge.html
(Obviously a pretty silly challenge, but hey.)
With some help from int-e in irc:
{-# OPTIONS_GHC -fglasgow-exts #-}
import GHC.Base import GHC.Word import GHC.Exts import Numeric import Data.Char
doubleToBits (D# d) = W64# (unsafeCoerce# d)
main = interact $ unlines . map (pad . (\x -> showIntAtBase 2 intToDigit x "") . doubleToBits . read) . lines where pad l = replicate (64 - length l) '0' ++ l
I suspect that that doesn't respect the endianness of the machine like the C++ does, though. -- Dan

On Thu, May 31, 2007 at 08:47:28PM +0100, Andrew Coppin wrote:
My first instinct was to use Data.Bits - but I see no instance for Double. (Presumably because performing bitwise operations on a Double is a pretty odd thing to want to do.) So my next guess is to do some bizzare type system hackery that allows you to transform a Double into... whichever integer type is the same size, and proceed from there. Does anybody know how to do that?
This reminds me. it would be nice if we could remove the 'Num' superclass of Bits, having bitwise operations and being a number are fairly unrelated and having to declare bogus instances is annoying. It is probably just a holdover from C that we think of them as related. 'Bool' would be a simple example of something that is a good instance of bits, but not Num. John -- John Meacham - ⑆repetae.net⑆john⑈

On Thu, May 31, 2007 at 08:47:28PM +0100, Andrew Coppin wrote:
If you're bored... can you come up with a solution to this?
http://warp.povusers.org/ProgrammingChallenge.html
(Obviously a pretty silly challenge, but hey.)
My first instinct was to use Data.Bits - but I see no instance for Double.
You can imitate the C++ code using the FFI libraries: import Foreign.Storable import Foreign import Data.Word import Data.Bits getDoubleBits :: Double -> IO String getDoubleBits d = alloca $ \ptr -> do poke ptr d bs <- peekArray (sizeOf d) (castPtr ptr :: Ptr Word8) return . concatMap (concatMap (show . fromEnum) . flip map [7,6..0] . testBit) $ bs (I'm not sure this code prints bits in the right order). You can generalize this to getStorableBits :: Storable a => a -> IO String Best regards Tomek

On Thu, May 31, 2007 at 11:36:54PM +0200, Tomasz Zielonka wrote:
You can imitate the C++ code using the FFI libraries:
import Foreign.Storable import Foreign import Data.Word import Data.Bits
getDoubleBits :: Double -> IO String getDoubleBits d = alloca $ \ptr -> do poke ptr d bs <- peekArray (sizeOf d) (castPtr ptr :: Ptr Word8) return . concatMap (concatMap (show . fromEnum) . flip map [7,6..0] . testBit) $ bs
(I'm not sure this code prints bits in the right order). You can generalize this to getStorableBits :: Storable a => a -> IO String
Note also that you can use unsafePerformIO to safely get pure functions doing both these operations. -- David Roundy Department of Physics Oregon State University

On Fri, Jun 01, 2007 at 07:28:07PM +0100, Andrew Coppin wrote:
David Roundy wrote:
Note also that you can use unsafePerformIO to safely get pure functions doing both these operations.
I've always been puzzled by this one... how does unsafePerformIO circumvent the type system? I don't understand.
It's a primitive. You couldn't implement it unless you're the compiler-writer. But it's a necesary primitive, if you wish to build efficient data types. You just need to carefully audit everywhere that unsafePerformIO is used. -- David Roundy Department of Physics Oregon State University

David Roundy wrote:
On Fri, Jun 01, 2007 at 07:28:07PM +0100, Andrew Coppin wrote:
David Roundy wrote:
Note also that you can use unsafePerformIO to safely get pure functions doing both these operations.
I've always been puzzled by this one... how does unsafePerformIO circumvent the type system? I don't understand.
It's a primitive. You couldn't implement it unless you're the compiler-writer. But it's a necesary primitive, if you wish to build efficient data types. You just need to carefully audit everywhere that unsafePerformIO is used.
No, I mean... how could you use unsafePerformIO to perform a typecast? I don't see a way to do that.

On Fri, Jun 01, 2007 at 07:39:32PM +0100, Andrew Coppin wrote:
David Roundy wrote:
On Fri, Jun 01, 2007 at 07:28:07PM +0100, Andrew Coppin wrote:
David Roundy wrote:
Note also that you can use unsafePerformIO to safely get pure functions doing both these operations.
I've always been puzzled by this one... how does unsafePerformIO circumvent the type system? I don't understand.
It's a primitive. You couldn't implement it unless you're the compiler-writer. But it's a necesary primitive, if you wish to build efficient data types. You just need to carefully audit everywhere that unsafePerformIO is used.
No, I mean... how could you use unsafePerformIO to perform a typecast? I don't see a way to do that.
Then I'm confused. What typecast are you talking about? -- David Roundy Department of Physics Oregon State University

David Roundy wrote:
On Fri, Jun 01, 2007 at 07:39:32PM +0100, Andrew Coppin wrote:
No, I mean... how could you use unsafePerformIO to perform a typecast? I don't see a way to do that.
Then I'm confused. What typecast are you talking about?
cast :: a -> b cast x = unsafePerformIO (do writeIORef r x; readIORef r) where r = unsafePerformIO (newIORef undefined) The problem is that the Hindley/Milner type inference algorithm is unsound in the presence of effects - r may not be given polymorphic type. That's exactly the reason for ML's dreaded value restriction. - Andreas

On Friday 01 June 2007, Andrew Coppin wrote:
David Roundy wrote:
Note also that you can use unsafePerformIO to safely get pure functions doing both these operations.
I've always been puzzled by this one... how does unsafePerformIO circumvent the type system? I don't understand.
import Data.IORef import System.IO.Unsafe ref :: IORef a ref = unsafePerformIO $ newIORef undefined cast :: a -> b cast a = unsafePerformIO $ do writeIORef ref a ; readIORef ref *Main> cast 2 :: Double -3.824225156758791e-48 *Main> -- Dan

On May 31, 2007, at 15:47 , Andrew Coppin wrote:
If you're bored... can you come up with a solution to this?
Is it me, or does this look like a job for Data.Binary? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 5/31/07, Brandon S. Allbery KF8NH
On May 31, 2007, at 15:47 , Andrew Coppin wrote:
If you're bored... can you come up with a solution to this?
Is it me, or does this look like a job for Data.Binary?
It's not just you. When I read it I thought "First I'd steal code from Data.Binary..."

Hello Andrew, Thursday, May 31, 2007, 11:47:28 PM, you wrote:
(Otherwise... wasn't there some library somewhere for serialising values in binary?)
Binary, AltBinary (see latest HCAR), just an example using AltBinary: main = do let s = encode (1.1::Float) -- s has type String print (decode s::Float, s) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bulat.ziganshin:
Hello Andrew,
Thursday, May 31, 2007, 11:47:28 PM, you wrote:
(Otherwise... wasn't there some library somewhere for serialising values in binary?)
Binary, AltBinary (see latest HCAR), just an example using AltBinary:
main = do let s = encode (1.1::Float) -- s has type String print (decode s::Float, s)
Data.Binary is on hackage, http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-0.3 encode :: (Binary a) => a -> ByteString decode :: (Binary a) => ByteString -> a > let s = encode (1.1 :: Float) > :t s s :: Data.ByteString.Lazy.ByteString > s LPS ["\NUL\NUL\140\204\205\255\255\255\255\255\255\255\233"] > decode s :: Float 1.1 See also the older NewBinary, http://hackage.haskell.org/cgi-bin/hackage-scripts/package/NewBinary-0.1 -- Don

Donald Bruce Stewart wrote:
> let s = encode (1.1 :: Float) > :t s s :: Data.ByteString.Lazy.ByteString > s LPS ["\NUL\NUL\140\204\205\255\255\255\255\255\255\255\233"]
> decode s :: Float 1.1
But doesn't Data.Binary serialise to a guaranteed representation, i.e. machine-independent? Whereas this (stupid) question explicitly asked for *your particular hardware's* floating point rep. Jules

jules:
Donald Bruce Stewart wrote:
let s = encode (1.1 :: Float) :t s s :: Data.ByteString.Lazy.ByteString s LPS ["\NUL\NUL\140\204\205\255\255\255\255\255\255\255\233"]
decode s :: Float 1.1
But doesn't Data.Binary serialise to a guaranteed representation, i.e. machine-independent? Whereas this (stupid) question explicitly asked for *your particular hardware's* floating point rep.
Ah right. Missed that. There was a long thread on the libraries@ mailing list on doing this (David Roundy suggested it, initially, iirc) a couple of months ago. Might be useful to read. -- Don

Hello Jules, Friday, June 1, 2007, 3:02:33 PM, you wrote:
machine-independent? Whereas this (stupid) question explicitly asked for *your particular hardware's* floating point rep.
there is castSTUArray function which is widely used exactly for this purpose. look for examples of its usage in haskell code -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Donald Bruce Stewart wrote:
See also the older NewBinary, http://hackage.haskell.org/cgi-bin/hackage-scripts/package/NewBinary-0.1
Now that's just ironic... Incidentally, I've been thinking. You *might* want the binary representation of things if you were going to, say, compress or encrypt data before putting it into a file or whatever. Actually in Java (bleeeh) you can wrap things around a stream so that data gets compressed and transformed between where the program writes it, and where it hits the endpoint. Haskell doesn't have a library for this, and I don't immediately see how to implement one. It would be darn useful to have a standard setup for this though. That way, when somebody wants to implement a new way to do zlib compression or a SHA-256 implementation or... there will already be a standardised way to access the binary representation of data without having to write it to a file. (If any of that made sense...)?)

andrewcoppin:
Donald Bruce Stewart wrote:
See also the older NewBinary, http://hackage.haskell.org/cgi-bin/hackage-scripts/package/NewBinary-0.1
Now that's just ironic...
Incidentally, I've been thinking. You *might* want the binary representation of things if you were going to, say, compress or encrypt data before putting it into a file or whatever. Actually in Java (bleeeh) you can wrap things around a stream so that data gets compressed and transformed between where the program writes it, and where it hits the endpoint. Haskell doesn't have a library for this, and I don't immediately see how to implement one. It would be darn useful to have a standard setup for this though. That way, when somebody wants to implement a new way to do zlib compression or a SHA-256 implementation or... there will already be a standardised way to access the binary representation of data without having to write it to a file.
(If any of that made sense...)?)
Our zlib and bzlib2 bindings operate on in-memory lazy bytestrings. They thus provide: compress :: ByteString -> ByteString and its inverse. So you can chain them with decoding: writeFile "foo.gz" . compress . encode $ myvalue -- Don
participants (16)
-
Andrew Coppin
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Creighton Hogg
-
Dan Doel
-
David House
-
David Roundy
-
dons@cse.unsw.edu.au
-
Dougal Stanton
-
John Meacham
-
Jon Fairbairn
-
Jules Bean
-
Rafael Almeida
-
rossberg@ps.uni-sb.de
-
Tomasz Zielonka
-
Udo Stenzel