From fbf425fbef1c1e60fcdddfbd9b25976162725f97 Mon Sep 17 00:00:00 2001 From: joe Date: Sun, 24 Apr 2016 18:43:00 -0400 Subject: Refactored build of executable and library. --- lib/Base58.hs | 70 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 70 insertions(+) create mode 100644 lib/Base58.hs (limited to 'lib/Base58.hs') diff --git a/lib/Base58.hs b/lib/Base58.hs new file mode 100644 index 0000000..3c1a113 --- /dev/null +++ b/lib/Base58.hs @@ -0,0 +1,70 @@ +{-# LANGUAGE CPP #-} +module Base58 where + +#if !defined(VERSION_cryptonite) +import qualified Crypto.Hash.SHA256 as SHA256 +#else +import Crypto.Hash +import Data.ByteArray (convert) +#endif +import qualified Data.ByteString as S +import Data.Maybe +import Data.List +import Data.Word ( Word8 ) +import Control.Monad + +base58chars :: [Char] +base58chars = "123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz" + +base58digits :: [Char] -> Maybe [Int] +base58digits str = sequence mbs + where + mbs = map (flip elemIndex base58chars) str + +-- 5HueCGU8rMjxEXxiPuD5BDku4MkFqeZyd4dZ1jvhTVqvbTLvyTJ +base58_decode :: [Char] -> Maybe (Word8,[Word8]) +base58_decode str = do + ds <- base58digits str + let n = foldl' (\a b-> a*58 + b) 0 $ ( map fromIntegral ds :: [Integer] ) + rbytes = unfoldr getbyte n + getbyte d = do + guard (d/=0) + let (q,b) = d `divMod` 256 + return (fromIntegral b,q) + + let (rcksum,rpayload) = splitAt 4 $ rbytes + a_payload = reverse rpayload +#if !defined(VERSION_cryptonite) + hash_result = S.take 4 . SHA256.hash . SHA256.hash . S.pack $ a_payload +#else + hash_result = S.take 4 . convert $ digest + where digest = hash (S.pack a_payload) :: Digest SHA256 +#endif + expected_hash = S.pack $ reverse rcksum + (network_id,payload) = splitAt 1 a_payload + + network_id <- listToMaybe network_id + guard (hash_result==expected_hash) + return (network_id,payload) + +base58_encode :: S.ByteString -> String +base58_encode hsh = replicate zcount '1' ++ map (base58chars !!) (reverse rdigits) + where + zcount = S.length . S.takeWhile (==0) $ hsh +#if !defined(VERSION_cryptonite) + cksum = S.take 4 . SHA256.hash . SHA256.hash $ hsh +#else + cksum = S.take 4 (convert digest2 :: S.ByteString) + where digest2 = hash ( convert digest1 :: S.ByteString) :: Digest SHA256 + digest1 = hash hsh :: Digest SHA256 +#endif + n = foldl' (\a b->a*256+b) 0 . map asInteger $ concatMap S.unpack [hsh, cksum] + asInteger x = fromIntegral x :: Integer + rdigits = unfoldr getdigit n + where + getdigit d = do + guard (d/=0) + let (q,b) = d `divMod` 58 + return (fromIntegral b,q) + + -- cgit v1.2.3