-- Internal.hs: private utility functions -- Copyright © 2012 Clint Adams -- This software is released under the terms of the ISC license. -- (See the LICENSE file). module Codec.Encryption.OpenPGP.Internal ( countBits , beBSToInteger , integerToBEBS ) where import Data.Bits (testBit, shiftL, shiftR, (.&.)) import Data.ByteString (ByteString) import qualified Data.ByteString as B import Data.List (mapAccumR, unfoldr) import Data.Word (Word8, Word16) countBits :: ByteString -> Word16 countBits bs = fromIntegral (B.length bs * 8) - fromIntegral (go (B.head bs) 7) where go :: Word8 -> Int -> Word8 go _ 0 = 7 go n b = if testBit n b then 7 - fromIntegral b else go n (b-1) beBSToInteger :: ByteString -> Integer beBSToInteger = sum . snd . mapAccumR (\acc x -> (acc + 8, fromIntegral x `shiftL` acc)) 0 . B.unpack integerToBEBS :: Integer -> ByteString integerToBEBS = B.pack . reverse . unfoldr (\x -> if x == 0 then Nothing else Just ((fromIntegral x :: Word8) .&. 0xff, x `shiftR` 8))