Convert bits to bytes

What's the quickest/the best/a way of converting a series of bits into bytes? Ie, converting a [Bool] to a [Word8]. So if I had replicate 8 True ++ replicate 8 False :: [Bool], it would spit out [255,0] :: [Word8].

2010/9/2 Alec Benzer
What's the quickest/the best/a way of converting a series of bits into bytes? Ie, converting a [Bool] to a [Word8]. So if I had replicate 8 True ++ replicate 8 False :: [Bool], it would spit out [255,0] :: [Word8].
Simple way : l = [False,False,False,True,False,False,True] foldl' (\a b -> a*2 + if b then 1 else 0) 0 l

2010/9/2 David Virebayre
Simple way :
l = [False,False,False,True,False,False,True] foldl' (\a b -> a*2 + if b then 1 else 0) 0 l
Oh sorry I answered too quickly and didn't see the list can have more than 8 bits. chunk :: [Bool] -> [[ Bool ]] chunk [] = [] chunk l = a : chunk b where (a,b) = splitAt 8 l conv1 = foldl' (\a b -> a*2 + if b then 1 else 0) 0 convlist = map conv1 . chunk test = convlist (replicate 8 True ++ replicate 8 False :: [Bool] )

I could have been a bit more verbose. The way I see it, since you have an arbitrary long list of 'bits' that you want to convert into bytes, the first thing to do is to group this list into sublists of 8 bits. That's what chunk does: it splits the list at the 8th element, and recursively does it for the rest of the list, until the list is empty. One problem with that is that if the length of the list isn't a multiple of 8, then the last byte might be incorrect.
chunk :: [Bool] -> [[ Bool ]] chunk [] = [] chunk l = a : chunk b where (a,b) = splitAt 8 l
This one converts a list of 'bits' into a number. The head of the list is assumed to be the most significant bit :
conv1 = foldl' (\a b -> a*2 + if b then 1 else 0) 0
if we want the head of the list to be the least significant bit, then you can convert with foldr :
conv1' = foldr (\b a -> a*2 + if b then 1 else 0) 0
Now converting the whole list is just a matter converting the whole list in groups, then converting each group :
convlist = map conv1 . chunk
test = convlist (replicate 8 True ++ replicate 8 False :: [Bool] )
David.

Thanks - I thought there would be some api for it but I see it's pretty
simple to do on your own.
I came up with this (dealing with non-multiple of 8 numbers of bits)
bitsToBytes :: [Bool] -> [Word8]
bitsToBytes [] = []
bitsToBytes bits = map bitsToByte (getChunks bits)
where bitsToByte = foldl' (\byte bit -> byte*2 + if bit then 1 else 0) 0
getChunks :: [Bool] -> [[Bool]]
getChunks [] = []
getChunks xs
| length xs < 8 = getChunks $ take 8 (xs ++ repeat False)
| otherwise =
let (these,rest) = splitAt 8 xs
in these:getChunks rest
On Thu, Sep 2, 2010 at 3:18 AM, David Virebayre
wrote:
I could have been a bit more verbose.
The way I see it, since you have an arbitrary long list of 'bits' that you want to convert into bytes, the first thing to do is to group this list into sublists of 8 bits.
That's what chunk does: it splits the list at the 8th element, and recursively does it for the rest of the list, until the list is empty.
One problem with that is that if the length of the list isn't a multiple of 8, then the last byte might be incorrect.
chunk :: [Bool] -> [[ Bool ]] chunk [] = [] chunk l = a : chunk b where (a,b) = splitAt 8 l
This one converts a list of 'bits' into a number. The head of the list is assumed to be the most significant bit :
conv1 = foldl' (\a b -> a*2 + if b then 1 else 0) 0
if we want the head of the list to be the least significant bit, then you can convert with foldr :
conv1' = foldr (\b a -> a*2 + if b then 1 else 0) 0
Now converting the whole list is just a matter converting the whole list in groups, then converting each group :
convlist = map conv1 . chunk
test = convlist (replicate 8 True ++ replicate 8 False :: [Bool] )
David.

Whoops, realized bitsToBytes [] = [] wasn't necessary.
On Thu, Sep 2, 2010 at 1:29 PM, Alec Benzer
Thanks - I thought there would be some api for it but I see it's pretty simple to do on your own.
I came up with this (dealing with non-multiple of 8 numbers of bits)
bitsToBytes :: [Bool] -> [Word8] bitsToBytes [] = [] bitsToBytes bits = map bitsToByte (getChunks bits) where bitsToByte = foldl' (\byte bit -> byte*2 + if bit then 1 else 0) 0
getChunks :: [Bool] -> [[Bool]] getChunks [] = [] getChunks xs | length xs < 8 = getChunks $ take 8 (xs ++ repeat False) | otherwise = let (these,rest) = splitAt 8 xs in these:getChunks rest
On Thu, Sep 2, 2010 at 3:18 AM, David Virebayre < dav.vire+haskell@gmail.com
> wrote: I could have been a bit more verbose.
The way I see it, since you have an arbitrary long list of 'bits' that you want to convert into bytes, the first thing to do is to group this list into sublists of 8 bits.
That's what chunk does: it splits the list at the 8th element, and recursively does it for the rest of the list, until the list is empty.
One problem with that is that if the length of the list isn't a multiple of 8, then the last byte might be incorrect.
chunk :: [Bool] -> [[ Bool ]] chunk [] = [] chunk l = a : chunk b where (a,b) = splitAt 8 l
This one converts a list of 'bits' into a number. The head of the list is assumed to be the most significant bit :
conv1 = foldl' (\a b -> a*2 + if b then 1 else 0) 0
if we want the head of the list to be the least significant bit, then you can convert with foldr :
conv1' = foldr (\b a -> a*2 + if b then 1 else 0) 0
Now converting the whole list is just a matter converting the whole list in groups, then converting each group :
convlist = map conv1 . chunk
test = convlist (replicate 8 True ++ replicate 8 False :: [Bool] )
David.

On Thursday 02 September 2010 19:29:23, Alec Benzer wrote:
I came up with this (dealing with non-multiple of 8 numbers of bits)
bitsToBytes :: [Bool] -> [Word8] bitsToBytes [] = [] bitsToBytes bits = map bitsToByte (getChunks bits) where bitsToByte = foldl' (\byte bit -> byte*2 + if bit then 1 else 0) 0
getChunks :: [Bool] -> [[Bool]] getChunks [] = [] getChunks xs | length xs < 8 = getChunks $ take 8 (xs ++ repeat False)
Pet peeve. Don't use `length xs < k' (or <=, ==, >=, >). That fails hard on infinite lists, also it is slow and prone to cause a space leak on long lists. Remember, length must walk the entire list. Instead of length xs < k use null (drop (k-1) xs), other combinations of not, null and drop for the other tests. Or you can use lazy Peano numbers and check genericLength xs < (8 :: Peano).
| otherwise = let (these,rest) = splitAt 8 xs in these:getChunks rest

Alec Benzer
What's the quickest/the best/a way of converting a series of bits into bytes? Ie, converting a [Bool] to a [Word8]. So if I had replicate 8 True ++ replicate 8 False :: [Bool], it would spit out [255,0] :: [Word8].
Here is my variant: import Data.Bits chunks :: Int -> [a] -> [[a]] chunks n = takeWhile (not . null) . map (take n) . iterate (drop n) boolToDigit :: Num i => Bool -> i boolToDigit False = 0 boolToDigit True = 1 bitsToByte :: Num i => [Bool] -> i bitsToByte = sum . zipWith (*) (iterate (*2) 1) . map boolToDigit bitsToBytes :: Bits i => [Bool] -> [i] bitsToBytes x = y where ~y@(y0:ys) = map bitsToByte . chunks (bitSize y0) $ x It works for every binary type with a fixed length, so you can use it with Word8, Word16, etc. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (4)
-
Alec Benzer
-
Daniel Fischer
-
David Virebayre
-
Ertugrul Soeylemez