convert a list of booleans into Word*

Hello, I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32. I have written one which seems very inefficient : toWord8 :: [Bool] -> Word8 toWord8 bs = go 0 0 bs where go n r [] = r go n r (b:bs) = go (n+1) (if b then setBit r n else clearBit r n) bs Is there a better way to do this out there ? (If it helps, i'm writting a toy compression algorithm, which outputs binary as lists of booleans, and I'd like to output that in a file). Cheers Paul

Paul.Brauner@loria.fr wrote:
(If it helps, i'm writting a toy compression algorithm, which outputs binary as lists of booleans, and I'd like to output that in a file).
By a strange coincidence, I did the self same thing a while back. There is Data.Binary which supports efficient reading and writing of binary data. However, sadly it does not support bit alignment, only whole byte alignment. I did put together a library to fix this, but I don't have the source code any more. Maybe I should finish it and put it on Hackage...

I wrote a few variants for fun. Probably equally inefficient. I suggest you look at Data.Binary as Andrew suggested. -- Your original function, but with a more generic type signature. encodeBits :: Bits n => [Bool] -> n encodeBits bs = go 0 0 bs where go n r [] = r go n r (b:bs) = go (n+1) (if b then setBit r n else clearBit r n) bs -- Combine the flags with their index and then set bits when appropriate. encodeBits2 :: Bits n => [Bool] -> n encodeBits2 = foldr (\(n, b) x -> setBitIf b x n) 0 . zip [0..] where setBitIf False x _ = x setBitIf True x n = setBit x n -- Shift the result left while constructing and only toggle the first bit. encodeBits3 :: Bits n => [Bool] -> n encodeBits3 bs = foldr (\b x -> setBitIf b (x `shiftL` 1)) 0 bs where setBitIf False x = x setBitIf True x = setBit x 0

Here's another approach for Bool lists with msb leftmost: bitsToInt :: [Bool] -> Integer bitsToInt = foldr((.(flip shiftL 1)).(+)) 0. map (fromIntegral.fromEnum) Hallo Paul.Brauner@loria.fr, je schreef op 30-09-09 11:18:
Hello,
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
I have written one which seems very inefficient :
toWord8 :: [Bool] -> Word8 toWord8 bs = go 0 0 bs where go n r [] = r go n r (b:bs) = go (n+1) (if b then setBit r n else clearBit r n) bs
Is there a better way to do this out there ?
(If it helps, i'm writting a toy compression algorithm, which outputs binary as lists of booleans, and I'd like to output that in a file).
Cheers Paul _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Met vriendelijke groet, =@@i

Sorry, msb rigthmost
Here's another approach for Bool lists with msb leftmost:
bitsToInt :: [Bool] -> Integer bitsToInt = foldr((.(flip shiftL 1)).(+)) 0. map (fromIntegral.fromEnum)
Hallo Paul.Brauner@loria.fr, je schreef op 30-09-09 11:18:
Hello,
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
I have written one which seems very inefficient :
toWord8 :: [Bool] -> Word8 toWord8 bs = go 0 0 bs where go n r [] = r go n r (b:bs) = go (n+1) (if b then setBit r n else clearBit r n) bs
Is there a better way to do this out there ?
(If it helps, i'm writting a toy compression algorithm, which outputs binary as lists of booleans, and I'd like to output that in a file).
Cheers Paul _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Met vriendelijke groet, =@@i

Very fast for long boolean lists by using a strict foldl and reversing the input: bsToInt :: [Bool] -> Integer bsToInt = foldl' ((.fromIntegral.fromEnum).(+).join(+)) 0. reverse Try this: (>1) $ bsToInt $ take 100000 $ cycle [True,True,False,True,True,False,True]
bitsToInt :: [Bool] -> Integer bitsToInt = foldr((.(flip shiftL 1)).(+)) 0. map (fromIntegral.fromEnum)
-- Met vriendelijke groet, =@@i

Thanks for the answers. I already had a look at Binary but, as said above, it doesn't support bit manipulation, only bytes. On Wed, Sep 30, 2009 at 11:18:03AM +0200, Paul.Brauner@loria.fr wrote:
Hello,
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
I have written one which seems very inefficient :
toWord8 :: [Bool] -> Word8 toWord8 bs = go 0 0 bs where go n r [] = r go n r (b:bs) = go (n+1) (if b then setBit r n else clearBit r n) bs
Is there a better way to do this out there ?
(If it helps, i'm writting a toy compression algorithm, which outputs binary as lists of booleans, and I'd like to output that in a file).
Cheers Paul _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Paul, Wednesday, September 30, 2009, 1:18:03 PM, you wrote:
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
sum . zipWith (*) (map (2^) [0..]) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Paul,
Wednesday, September 30, 2009, 1:18:03 PM, you wrote:
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
sum . zipWith (*) (map (2^) [0..])
I'd turn this into
sum . zipWith (*) (iterate (2*) 1) , but it's probably not very important.
Regards, Jochem -- Jochem Berndsen | jochem@functor.nl | jochem@牛在田里.com

...Or let's fuse it.
sum . zipWith ((*).(2^)) [0..]
2009/9/30 Jochem Berndsen
Bulat Ziganshin wrote:
Hello Paul,
Wednesday, September 30, 2009, 1:18:03 PM, you wrote:
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
sum . zipWith (*) (map (2^) [0..])
I'd turn this into
sum . zipWith (*) (iterate (2*) 1) , but it's probably not very important.
Regards, Jochem -- Jochem Berndsen | jochem@functor.nl | jochem@牛在田里.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

On Wed, 30 Sep 2009, Jochem Berndsen wrote:
Bulat Ziganshin wrote:
Hello Paul,
Wednesday, September 30, 2009, 1:18:03 PM, you wrote:
I haven't found a function in hackage or in the standard library that takes a list of booleans (or a list of 0s and 1s, or a tuple of booleans or 0s and 1s) and outputs a Word8 or Word32.
sum . zipWith (*) (map (2^) [0..])
I'd turn this into
sum . zipWith (*) (iterate (2*) 1) , but it's probably not very important.
Or sum . zipWith (*) (iterate (flip shiftL 1) 1) . map fromEnum in order to make the bitset nature more explicit.

Bulat Ziganshin-2 wrote:
sum . zipWith (*) (map (2^) [0..])
foldr1 $ \b -> (+b) . (*2) -- View this message in context: http://www.nabble.com/convert-a-list-of-booleans-into-Word*-tp25677589p25686... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
participants (9)
-
Aai
-
Andrew Coppin
-
Bulat Ziganshin
-
Eduard Sergeev
-
Eugene Kirpichov
-
Henning Thielemann
-
Jochem Berndsen
-
Paul.Brauner@loria.fr
-
Roel van Dijk