summaryrefslogtreecommitdiff
path: root/Base58.hs
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2016-04-14 14:48:26 -0400
committerjoe <joe@jerkface.net>2016-04-14 14:48:26 -0400
commit13f3a96ae0a1417e15c9f969737c512ec71642f9 (patch)
tree2f5ce83fb1f4e18ce4a5020c62dbf449859912e0 /Base58.hs
parent71469bfd192b3be62b5c51aeeba37620785bda4b (diff)
Updated build.
Diffstat (limited to 'Base58.hs')
-rw-r--r--Base58.hs25
1 files changed, 21 insertions, 4 deletions
diff --git a/Base58.hs b/Base58.hs
index de35b01..3c1a113 100644
--- a/Base58.hs
+++ b/Base58.hs
@@ -1,6 +1,12 @@
1{-# LANGUAGE CPP #-}
1module Base58 where 2module Base58 where
2 3
4#if !defined(VERSION_cryptonite)
3import qualified Crypto.Hash.SHA256 as SHA256 5import qualified Crypto.Hash.SHA256 as SHA256
6#else
7import Crypto.Hash
8import Data.ByteArray (convert)
9#endif
4import qualified Data.ByteString as S 10import qualified Data.ByteString as S
5import Data.Maybe 11import Data.Maybe
6import Data.List 12import Data.List
@@ -28,7 +34,12 @@ base58_decode str = do
28 34
29 let (rcksum,rpayload) = splitAt 4 $ rbytes 35 let (rcksum,rpayload) = splitAt 4 $ rbytes
30 a_payload = reverse rpayload 36 a_payload = reverse rpayload
37#if !defined(VERSION_cryptonite)
31 hash_result = S.take 4 . SHA256.hash . SHA256.hash . S.pack $ a_payload 38 hash_result = S.take 4 . SHA256.hash . SHA256.hash . S.pack $ a_payload
39#else
40 hash_result = S.take 4 . convert $ digest
41 where digest = hash (S.pack a_payload) :: Digest SHA256
42#endif
32 expected_hash = S.pack $ reverse rcksum 43 expected_hash = S.pack $ reverse rcksum
33 (network_id,payload) = splitAt 1 a_payload 44 (network_id,payload) = splitAt 1 a_payload
34 45
@@ -37,11 +48,17 @@ base58_decode str = do
37 return (network_id,payload) 48 return (network_id,payload)
38 49
39base58_encode :: S.ByteString -> String 50base58_encode :: S.ByteString -> String
40base58_encode hash = replicate zcount '1' ++ map (base58chars !!) (reverse rdigits) 51base58_encode hsh = replicate zcount '1' ++ map (base58chars !!) (reverse rdigits)
41 where 52 where
42 zcount = S.length . S.takeWhile (==0) $ hash 53 zcount = S.length . S.takeWhile (==0) $ hsh
43 cksum = S.take 4 . SHA256.hash . SHA256.hash $ hash 54#if !defined(VERSION_cryptonite)
44 n = foldl' (\a b->a*256+b) 0 . map asInteger $ concatMap S.unpack [hash, cksum] 55 cksum = S.take 4 . SHA256.hash . SHA256.hash $ hsh
56#else
57 cksum = S.take 4 (convert digest2 :: S.ByteString)
58 where digest2 = hash ( convert digest1 :: S.ByteString) :: Digest SHA256
59 digest1 = hash hsh :: Digest SHA256
60#endif
61 n = foldl' (\a b->a*256+b) 0 . map asInteger $ concatMap S.unpack [hsh, cksum]
45 asInteger x = fromIntegral x :: Integer 62 asInteger x = fromIntegral x :: Integer
46 rdigits = unfoldr getdigit n 63 rdigits = unfoldr getdigit n
47 where 64 where