Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Hash = Hash {
- unHash :: ByteString
- data Trie a = Trie {}
- data TrieNode a
- data NodeType
- data TrieLocation = TrieLocation {}
- degree :: Int
- class HasDigest a where
- data Fingerprint = Fingerprint {
- f_hash :: Hash
- f_nodeType :: NodeType
- toFingerprint :: Trie a -> Fingerprint
- mkTrie :: (Ord a, HasDigest a) => Int -> [a] -> Trie a
- mkNode :: Array Int (Trie a) -> Trie a
- hashSHA256 :: ByteString -> Digest SHA256
- combineHash :: [Hash] -> Hash
- groupOf :: HasDigest a => Int -> a -> Int
- mkLeave :: (HasDigest a, Ord a) => [a] -> Trie a
- lookup :: Monad m => Trie a -> TrieLocation -> m (Trie a)
- queryHash :: Monad m => Trie a -> TrieLocation -> m Fingerprint
- querySet :: (Ord a, Monad m) => Trie a -> TrieLocation -> m (Set a)
- getAll :: Ord a => Trie a -> Set a
- rootLocation :: TrieLocation
- expand :: TrieLocation -> Array Int (Trie a) -> [(TrieLocation, Trie a)]
- newtype TestDigest = TestDigest {
- unTestDigest :: Text
- tests :: Test
Documentation
Hash | |
|
data Fingerprint Source
Fingerprint of a Merkle-Hash-Tree node We asssume the Tree below a node is identical while synchronizing if its FingerPrint is
Fingerprint | |
|
toFingerprint :: Trie a -> Fingerprint Source
mkTrie :: (Ord a, HasDigest a) => Int -> [a] -> Trie a Source
Creates a Merkle-Hash-Tree for a list of elements
hashSHA256 :: ByteString -> Digest SHA256 Source
combineHash :: [Hash] -> Hash Source
groupOf :: HasDigest a => Int -> a -> Int Source
The function groupOf x
eeturns a value between 0 to degree-1 for a digest with the property
that groupOf
forms an approximate unviversal hash familiy.
queryHash :: Monad m => Trie a -> TrieLocation -> m Fingerprint Source
expand :: TrieLocation -> Array Int (Trie a) -> [(TrieLocation, Trie a)] Source
newtype TestDigest Source