module Data.Locator.Hashes (
toBase62,
fromBase62,
padWithZeros,
hashStringToBase62
) where
import Prelude hiding (toInteger)
import Crypto.Hash.SHA1 as Crypto
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as S
import Data.Char (chr, isDigit, isLower, isUpper, ord)
import Data.Word
import Numeric (showIntAtBase)
represent :: Int -> Char
represent x
| x < 10 = chr (48 + x)
| x < 36 = chr (65 + x 10)
| x < 62 = chr (97 + x 36)
| otherwise = '@'
toBase62 :: Integer -> String
toBase62 x =
showIntAtBase 62 represent x ""
padWithZeros :: Int -> String -> String
padWithZeros digits str =
pad ++ str
where
pad = take len (replicate digits '0')
len = digits length str
value :: Char -> Int
value c
| isDigit c = ord c 48
| isUpper c = ord c 65 + 10
| isLower c = ord c 97 + 36
| otherwise = 0
multiply :: Integer -> Char -> Integer
multiply acc c =
acc * 62 + (fromIntegral $ value c)
fromBase62 :: String -> Integer
fromBase62 ss =
foldl multiply 0 ss
concatToInteger :: [Word8] -> Integer
concatToInteger bytes =
foldl fn 0 bytes
where
fn acc b = (acc * 256) + (fromIntegral b)
digest :: String -> Integer
digest ws =
i
where
i = concatToInteger h
h = B.unpack h'
h' = Crypto.hash x'
x' = S.pack ws
hashStringToBase62 :: Int -> ByteString -> ByteString
hashStringToBase62 digits s' =
r'
where
s = S.unpack s'
n = digest s
limit = 62 ^ digits
x = mod n limit
str = toBase62 x
r = padWithZeros digits str
r' = S.pack r