module Distribution.Nixpkgs.Hashes ( printSHA256, packHex ) where
import Control.Exception ( assert )
import Data.Bits
import Data.ByteString ( ByteString )
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import Data.Char
import Data.Word
base32chars :: ByteString
base32chars = BSC.pack "0123456789abcdfghijklmnpqrsvwxyz";
printSHA256 :: ByteString -> String
printSHA256 buf = assert (BS.length buf == 32) $
map (BSC.index base32chars . fromIntegral . getQuintet buf) [51,50..0]
getQuintet :: ByteString -> Int -> Word8
getQuintet buf n = (c1 .|. c2) .&. 0x1f
where
b = n * 5
(i,j) = b `divMod` 8
c1 = BS.index buf i `shiftR` j
c2 = if i >= 31 then 0 else BS.index buf (i+1) `shiftL` (8j)
packHex :: String -> ByteString
packHex = BS.pack . hex2bin
hex2bin :: String -> [Word8]
hex2bin input = f $ (if even (length input) then id else ('0':)) input
where
f :: String -> [Word8]
f [] = []
f [x] = [digit x]
f (x1:x2:xs) = ((digit x1 `shiftL` 4) .|. digit x2) : f xs
digit :: Char -> Word8
digit = fromIntegral . digitToInt