#3563: A couple of additions to Data.Bits
-----------------------------+----------------------------------------------
Reporter:  porges            |          Owner:                  
    Type:  proposal          |         Status:  new             
Priority:  normal            |      Component:  libraries/base  
 Version:  6.11              |       Severity:  normal          
Keywords:                    |       Testcase:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-----------------------------+----------------------------------------------
 Population count is an often-needed function when bitfiddling, so I think
 a version should be supplied. I also have included functions for
 converting to and from lists of Booleans:

 {{{
 -- population count
 popCount :: (Bits a, Num t) => a -> t
 popCount x = count' (bitSize x) x 0
   where
   count' 0 _ acc = acc
   count' n x acc = count' (n-1) (x `shiftR` 1) (acc + if x .&. 1 == 1 then
 1 else 0)
                 -- this weird if/else is to preserve the nice type
 signature :)

 -- converts a list of bools to a number
 fromBools :: (Bits a) => [Bool] -> a
 fromBools = foldl' (\i b -> (i `shiftL` 1) .|. if b then 1 else 0) 0 --
 likewise

 -- converts a number to a list of bools
 toBools :: (Bits a) => a -> [Bool]
 toBools x = reverse (toBools' (bitSize x) x)
   where
   toBools' 0 _ = []
   toBools' n x = (x .&. 1 == 1) : toBools' (n-1) (x `shiftR` 1)

 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3563>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to