| Copyright | 2018 Monadic GmbH |
|---|---|
| License | BSD3 |
| Maintainer | kim@monadic.xyz, team@monadic.xyz |
| Stability | provisional |
| Portability | non-portable (GHC extensions) |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Multihash
Contents
Description
multihash encoding of Digests.
Example:
>>>:set -XOverloadedStrings>>>import qualified Crypto.Hash as C>>>import Data.ByteArray.Encoding (Base(..), convertToBase)>>>import Data.ByteString (ByteString)>>>import qualified Data.ByteString.Char8 as C8>>>import System.IO (stdout)>>>:{let input :: ByteString input = "multihash" atBase :: Base -> Multihash -> ByteString atBase base = convertToBase base . encodedBytes in C8.hPutStr stdout $ C8.unlines [ atBase Base16 $ multihash C.SHA1 input , atBase Base32 $ multihash C.SHA1 input , atBase Base16 $ multihash C.SHA256 input , atBase Base32 $ multihash C.SHA256 input ] :} 111488c2f11fb2ce392acb5b2986e640211c4690073e CEKIRQXRD6ZM4OJKZNNSTBXGIAQRYRUQA47A==== 12209cbc07c3f991725836a3aa2a581ca2029198aa420b9d99bc0e131d9f3e2cbe47 CIQJZPAHYP4ZC4SYG2R2UKSYDSRAFEMYVJBAXHMZXQHBGHM7HYWL4RY=
Synopsis
- data Multihash
- fromDigest :: forall a. Multihashable a => Digest a -> Multihash
- encodedBytes :: Multihash -> ByteString
- multihash :: (ByteArrayAccess ba, Multihashable a) => a -> ba -> Multihash
- decode :: ByteString -> Either String Multihash
- decodeDigest :: forall a. Multihashable a => ByteString -> Either String (Digest a)
- getMultihash :: Get Multihash
- data CompactMultihash
- compact :: Multihash -> CompactMultihash
- expand :: CompactMultihash -> Multihash
- data HashAlgorithm
- type Multihashable a = (HashAlgorithm a, FromCryptonite a)
- fromCryptonite :: FromCryptonite a => proxy a -> HashAlgorithm
- toCode :: HashAlgorithm -> Word16
- fromCode :: Word16 -> Maybe HashAlgorithm
- digestSize :: HashAlgorithm -> Int
Documentation
A multihash-encoded strict ByteString.
Instances
| Eq Multihash Source # | |
| Ord Multihash Source # | |
| NFData Multihash Source # | |
Defined in Data.Multihash | |
| Hashable Multihash Source # | |
Defined in Data.Multihash | |
fromDigest :: forall a. Multihashable a => Digest a -> Multihash Source #
encodedBytes :: Multihash -> ByteString Source #
Extract the raw, multihash-encoded bytes of a Multihash.
multihash :: (ByteArrayAccess ba, Multihashable a) => a -> ba -> Multihash Source #
Hash a value to a Multihash
decode :: ByteString -> Either String Multihash Source #
Decode a Multihash from a ByteString.
decodeDigest :: forall a. Multihashable a => ByteString -> Either String (Digest a) Source #
Decode a Digest from a multihash-encoded ByteString.
Compact representation
data CompactMultihash Source #
A Multihash backed by a ShortByteString.
This is useful when holding many Multihashes in memory, due to lower memory
overhead and less heap fragmentation. See the documentation for
ShortByteString for details.
Instances
| Eq CompactMultihash Source # | |
Defined in Data.Multihash Methods (==) :: CompactMultihash -> CompactMultihash -> Bool # (/=) :: CompactMultihash -> CompactMultihash -> Bool # | |
| Ord CompactMultihash Source # | |
Defined in Data.Multihash Methods compare :: CompactMultihash -> CompactMultihash -> Ordering # (<) :: CompactMultihash -> CompactMultihash -> Bool # (<=) :: CompactMultihash -> CompactMultihash -> Bool # (>) :: CompactMultihash -> CompactMultihash -> Bool # (>=) :: CompactMultihash -> CompactMultihash -> Bool # max :: CompactMultihash -> CompactMultihash -> CompactMultihash # min :: CompactMultihash -> CompactMultihash -> CompactMultihash # | |
| NFData CompactMultihash Source # | |
Defined in Data.Multihash Methods rnf :: CompactMultihash -> () # | |
| Hashable CompactMultihash Source # | |
Defined in Data.Multihash | |
expand :: CompactMultihash -> Multihash Source #
Convert a CompactMultihash to the regular representation.
Re-exports
data HashAlgorithm Source #
HashAlgorithms for which we know a multihash code.
Note that this currently excludes variable output-length algorithms.
Instances
| Bounded HashAlgorithm Source # | |
Defined in Data.Multihash.Internal | |
| Enum HashAlgorithm Source # | |
Defined in Data.Multihash.Internal Methods succ :: HashAlgorithm -> HashAlgorithm # pred :: HashAlgorithm -> HashAlgorithm # toEnum :: Int -> HashAlgorithm # fromEnum :: HashAlgorithm -> Int # enumFrom :: HashAlgorithm -> [HashAlgorithm] # enumFromThen :: HashAlgorithm -> HashAlgorithm -> [HashAlgorithm] # enumFromTo :: HashAlgorithm -> HashAlgorithm -> [HashAlgorithm] # enumFromThenTo :: HashAlgorithm -> HashAlgorithm -> HashAlgorithm -> [HashAlgorithm] # | |
| Eq HashAlgorithm Source # | |
Defined in Data.Multihash.Internal Methods (==) :: HashAlgorithm -> HashAlgorithm -> Bool # (/=) :: HashAlgorithm -> HashAlgorithm -> Bool # | |
type Multihashable a = (HashAlgorithm a, FromCryptonite a) Source #
fromCryptonite :: FromCryptonite a => proxy a -> HashAlgorithm Source #
toCode :: HashAlgorithm -> Word16 Source #
digestSize :: HashAlgorithm -> Int Source #