forked from schmittlauch/Hash2Pub
buggy prototype of bytestring to UInteger conversion
This commit is contained in:
parent
8ad247978a
commit
2d05d0644d
|
@ -2,10 +2,14 @@
|
||||||
module Foo where
|
module Foo where
|
||||||
|
|
||||||
import Crypto.Hash
|
import Crypto.Hash
|
||||||
|
import Data.Word
|
||||||
|
import Data.Bits (shift)
|
||||||
|
import Network.Socket (HostAddress6)
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import qualified Data.ByteString.Builder as BB
|
import qualified Data.ByteString.Builder as BB
|
||||||
import qualified Data.ByteString.Lazy as BL
|
import qualified Data.ByteString.Lazy as BL
|
||||||
import qualified Data.ByteString.UTF8 as BSU
|
import qualified Data.ByteString.UTF8 as BSU
|
||||||
|
import qualified Data.Binary.Strict.Get as BinGet
|
||||||
import qualified Data.ByteArray as BA
|
import qualified Data.ByteArray as BA
|
||||||
|
|
||||||
-- important: only works with strict ByteStrings
|
-- important: only works with strict ByteStrings
|
||||||
|
@ -15,7 +19,8 @@ hashToShake128 string = hash bstr :: Digest (SHAKE128 128)
|
||||||
|
|
||||||
-- TODO: type signature
|
-- TODO: type signature
|
||||||
-- TODO: convert byte string to Integer (as separate function, useful for parsing later on)
|
-- TODO: convert byte string to Integer (as separate function, useful for parsing later on)
|
||||||
hashNodeID ipaddr@(a, b, _, _) domain vserver =
|
hashNodeIDBS :: HostAddress6 -> String -> Word8 -> BS.ByteString
|
||||||
|
hashNodeIDBS ipaddr@(a, b, _, _) domain vserver =
|
||||||
hashIpaddrUpper `BS.append` hashID domain' `BS.append` hashIpaddLower
|
hashIpaddrUpper `BS.append` hashID domain' `BS.append` hashIpaddLower
|
||||||
where
|
where
|
||||||
vsBS = BS.pack [vserver] -- attention: only works for vserver IDs up to 255
|
vsBS = BS.pack [vserver] -- attention: only works for vserver IDs up to 255
|
||||||
|
@ -25,4 +30,40 @@ hashNodeID ipaddr@(a, b, _, _) domain vserver =
|
||||||
hashID bstr = BS.pack . BA.unpack $ (hash bstr :: Digest (SHAKE128 128))
|
hashID bstr = BS.pack . BA.unpack $ (hash bstr :: Digest (SHAKE128 128))
|
||||||
(hashIpaddrUpper, hashIpaddLower) = BS.splitAt 64 $ hashID ipaddrNet
|
(hashIpaddrUpper, hashIpaddLower) = BS.splitAt 64 $ hashID ipaddrNet
|
||||||
|
|
||||||
testIDHash = hashNodeID (0x2001 + 0x16b8, 0x755a + 0xb1100, 0x7d6a + 0x12ab, 0xf0c5 + 0x386e) "example.com" 0
|
|
||||||
|
--hashNodeID = byteStringToUInteger hashNodeIDBS
|
||||||
|
|
||||||
|
|
||||||
|
-- | parses the bit pattern of a ByteString as an unsigned Integer in Big Endian order
|
||||||
|
-- by iterating it byte-wise from the back and shifting the byte values according to their offset
|
||||||
|
byteStringToUInteger :: BS.ByteString -> Integer
|
||||||
|
byteStringToUInteger bs = sum $ parsedBytes 0 bs
|
||||||
|
where
|
||||||
|
parsedBytes :: Integer -> BS.ByteString -> [ Integer ]
|
||||||
|
parsedBytes offset bs = case BS.unsnoc bs of
|
||||||
|
Nothing -> []
|
||||||
|
Just (bs, w) -> parseWithOffset offset w : parsedBytes (offset+1) bs
|
||||||
|
|
||||||
|
parseWithOffset :: Integer -> Word8 -> Integer
|
||||||
|
parseWithOffset 0 word = toInteger word -- a shift of 0 is always 0
|
||||||
|
parseWithOffset offset word = shift (toInteger word) 8*offset
|
||||||
|
|
||||||
|
-- |Utility function creating a strict ByteString from [Word32],
|
||||||
|
-- needed for encoding @HostAddress6@ as a ByteString
|
||||||
|
--packW32 :: [ Word32 ] -> BS.ByteString
|
||||||
|
--packW32 [] = BS.empty
|
||||||
|
--packW32 xs = map BinGet.
|
||||||
|
--
|
||||||
|
--w32ToBSParser :: BinGet.Get [Word8]
|
||||||
|
--w32ToBSParser = do
|
||||||
|
-- a <- getWord8
|
||||||
|
-- b <- getWord8
|
||||||
|
-- c <- getWord8
|
||||||
|
-- d <- getWord8
|
||||||
|
-- return [a, b, c, d]
|
||||||
|
|
||||||
|
|
||||||
|
--- test data ---
|
||||||
|
|
||||||
|
testIDHash = hashNodeIDBS (0x2001 + 0x16b8, 0x755a + 0xb1100, 0x7d6a + 0x12ab, 0xf0c5 + 0x386e) "example.com" 0
|
||||||
|
zweiHoch248 = BS.pack $ 1:replicate 31 0
|
||||||
|
|
Loading…
Reference in a new issue