Re: [Haskell-cafe] int to bin, bin to int

2007-09-28 Thread Brent Yorgey
On 9/27/07, PR Stanley [EMAIL PROTECTED] wrote:

 Hi
 intToBin :: Int - [Int]
 intToBin 1 = [1]
 intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

 binToInt :: [Integer] - Integer
 binToInt [] = 0
 binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)
 Any comments and/or criticisms on the above definitions would be
 appreciated.
 Thanks , Paul


Others have already given many good suggestions, but I'll add something
specifically about the order of the bits in the result. You have the
generated list of bits in reading order, i.e. high-order bits first.  But
perhaps it would make more sense to have the low-order bits first?  At
least, it would be more efficient that way.  Then you could do

intToBin n = (n `mod` 2) : (intToBin (n `div` 2)

The way you have it now, you will end up with something like [1] ++ [0] ++
[0] ++ [1] ++ ... which ends up inefficiently traversing the list multiple
times.  To undo, just (for example)

binToInt xs = sum $ zipWith (*) xs (iterate (*2) 1).

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] int to bin, bin to int

2007-09-27 Thread PR Stanley

Hi
intToBin :: Int - [Int]
intToBin 1 = [1]
intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

binToInt :: [Integer] - Integer
binToInt [] = 0
binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)
Any comments and/or criticisms on the above definitions would be appreciated.
Thanks , Paul

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] int to bin, bin to int

2007-09-27 Thread Don Stewart
prstanley:
 Hi
 intToBin :: Int - [Int]
 intToBin 1 = [1]
 intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]
 
 binToInt :: [Integer] - Integer
 binToInt [] = 0
 binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)

 Any comments and/or criticisms on the above definitions would be 
 appreciated.

One of my favourites is:

unroll :: Integer - [Word8]
unroll = unfoldr step
  where
  step 0 = Nothing
  step i = Just (fromIntegral i .. 1, i `shiftR` 1)

roll :: [Word8] - Integer
roll   = foldr unstep 0 
  where
  unstep b a = a `shiftL` 1 .|. fromIntegral b

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] int to bin, bin to int

2007-09-27 Thread Christopher L Conway
On 9/27/07, PR Stanley [EMAIL PROTECTED] wrote:
 Hi
 intToBin :: Int - [Int]
 intToBin 1 = [1]
 intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

 binToInt :: [Integer] - Integer
 binToInt [] = 0
 binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)
 Any comments and/or criticisms on the above definitions would be appreciated.
 Thanks , Paul

IntToBin diverges for inputs = 0. You could get 0 for free with

intToBin :: Int - [Int]
intToBin 0 = []
intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

And why not use [Bool] for the Bin type? Or

data Bin = Zero | One

Regards,
Chris
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] int to bin, bin to int

2007-09-27 Thread Rodrigo Queiro
If you don't like explicit recursion (or points):

intToBin = map (`mod` 2) . takeWhile (0) . iterate (`div` 2)

binToInt = foldl' (\n d - n*2+d) 0
or even:
binToInt = foldl' ((+).(*2)) 0

On 27/09/2007, PR Stanley [EMAIL PROTECTED] wrote:
 Hi
 intToBin :: Int - [Int]
 intToBin 1 = [1]
 intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

 binToInt :: [Integer] - Integer
 binToInt [] = 0
 binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)
 Any comments and/or criticisms on the above definitions would be appreciated.
 Thanks , Paul

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] int to bin, bin to int

2007-09-27 Thread Dan Weston

I might be inclined to use data Bin = Zero | One
(or at least type Bin = Bool) to let the type system guarantee that 
you'll only ever have binary digits in your [Bin], not any old integer.


Using [Int] is an abstraction leak, inviting people to abuse the 
representation behind your back.


Rodrigo Queiro wrote:

If you don't like explicit recursion (or points):

intToBin = map (`mod` 2) . takeWhile (0) . iterate (`div` 2)

binToInt = foldl' (\n d - n*2+d) 0
or even:
binToInt = foldl' ((+).(*2)) 0

On 27/09/2007, PR Stanley [EMAIL PROTECTED] wrote:

Hi
intToBin :: Int - [Int]
intToBin 1 = [1]
intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

binToInt :: [Integer] - Integer
binToInt [] = 0
binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)
Any comments and/or criticisms on the above definitions would be appreciated.
Thanks , Paul

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe