Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Abstract hashing functionality.
Synopsis
- class (KnownNat (SizeHash h), Typeable h) => HashAlgorithm h where
- type SizeHash h :: Nat
- hashAlgorithmName :: proxy h -> String
- digest :: proxy h -> ByteString -> ByteString
- sizeHash :: forall h proxy. HashAlgorithm h => proxy h -> Word
- data ByteString
- data Hash h a where
- pattern UnsafeHash :: forall h a. HashAlgorithm h => ShortByteString -> Hash h a
- data PackedBytes (n :: Nat) where
- PackedBytes8 :: !Word64 -> PackedBytes 8
- PackedBytes28 :: !Word64 -> !Word64 -> !Word64 -> !Word32 -> PackedBytes 28
- PackedBytes32 :: !Word64 -> !Word64 -> !Word64 -> !Word64 -> PackedBytes 32
- hashWith :: forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
- hashWithSerialiser :: forall h a. HashAlgorithm h => (a -> Encoding) -> a -> Hash h a
- castHash :: Hash h a -> Hash h b
- hashToBytes :: Hash h a -> ByteString
- hashFromBytes :: forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
- hashToBytesShort :: Hash h a -> ShortByteString
- hashFromBytesShort :: forall h a. HashAlgorithm h => ShortByteString -> Maybe (Hash h a)
- hashFromOffsetBytesShort :: forall h a. HashAlgorithm h => ShortByteString -> Int -> Maybe (Hash h a)
- hashToPackedBytes :: Hash h a -> PackedBytes (SizeHash h)
- hashFromPackedBytes :: PackedBytes (SizeHash h) -> Hash h a
- hashToBytesAsHex :: Hash h a -> ByteString
- hashFromBytesAsHex :: HashAlgorithm h => ByteString -> Maybe (Hash h a)
- hashToTextAsHex :: Hash h a -> Text
- hashFromTextAsHex :: HashAlgorithm h => Text -> Maybe (Hash h a)
- hashToStringAsHex :: Hash h a -> String
- hashFromStringAsHex :: HashAlgorithm h => String -> Maybe (Hash h a)
- xor :: Hash h a -> Hash h a -> Hash h a
- hash :: forall h a. (HashAlgorithm h, ToCBOR a) => a -> Hash h a
- fromHash :: Hash h a -> Natural
- hashRaw :: forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
- getHash :: Hash h a -> ByteString
- getHashBytesAsHex :: Hash h a -> ByteString
Documentation
class (KnownNat (SizeHash h), Typeable h) => HashAlgorithm h where Source #
hashAlgorithmName :: proxy h -> String Source #
digest :: proxy h -> ByteString -> ByteString Source #
Instances
sizeHash :: forall h proxy. HashAlgorithm h => proxy h -> Word Source #
The size in bytes of the output of digest
data ByteString Source #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
pattern UnsafeHash :: forall h a. HashAlgorithm h => ShortByteString -> Hash h a |
Instances
HashAlgorithm h => IsString (Q (TExp (Hash h a))) Source # | This instance is meant to be used with
|
Defined in Cardano.Crypto.Hash.Class | |
HashAlgorithm h => FromJSON (Hash h a) Source # | |
HashAlgorithm h => FromJSONKey (Hash h a) Source # | |
Defined in Cardano.Crypto.Hash.Class fromJSONKey :: FromJSONKeyFunction (Hash h a) Source # fromJSONKeyList :: FromJSONKeyFunction [Hash h a] Source # | |
HashAlgorithm h => ToJSON (Hash h a) Source # | |
HashAlgorithm h => ToJSONKey (Hash h a) Source # | |
Defined in Cardano.Crypto.Hash.Class toJSONKey :: ToJSONKeyFunction (Hash h a) Source # toJSONKeyList :: ToJSONKeyFunction [Hash h a] Source # | |
HashAlgorithm h => IsString (Hash h a) Source # | |
Defined in Cardano.Crypto.Hash.Class fromString :: String -> Hash h a Source # | |
Generic (Hash h a) Source # | |
HashAlgorithm h => Read (Hash h a) Source # | |
Show (Hash h a) Source # | |
(HashAlgorithm h, Typeable a) => FromCBOR (Hash h a) Source # | |
(HashAlgorithm h, Typeable a) => ToCBOR (Hash h a) Source # | |
NFData (Hash h a) Source # | |
Defined in Cardano.Crypto.Hash.Class | |
Eq (Hash h a) Source # | |
Ord (Hash h a) Source # | |
Defined in Cardano.Crypto.Hash.Class | |
HeapWords (Hash h a) Source # | |
NoThunks (Hash h a) Source # | |
type Rep (Hash h a) Source # | |
Defined in Cardano.Crypto.Hash.Class type Rep (Hash h a) = D1 ('MetaData "Hash" "Cardano.Crypto.Hash.Class" "cardano-crypto-class-2.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "UnsafeHashRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackedBytes (SizeHash h))))) |
data PackedBytes (n :: Nat) where Source #
PackedBytes8 :: !Word64 -> PackedBytes 8 | |
PackedBytes28 :: !Word64 -> !Word64 -> !Word64 -> !Word32 -> PackedBytes 28 | |
PackedBytes32 :: !Word64 -> !Word64 -> !Word64 -> !Word64 -> PackedBytes 32 |
Instances
Core operations
hashWith :: forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a Source #
Hash the given value, using a serialisation function to turn it into bytes.
hashWithSerialiser :: forall h a. HashAlgorithm h => (a -> Encoding) -> a -> Hash h a Source #
A variation on hashWith
, but specially for CBOR encodings.
Conversions
castHash :: Hash h a -> Hash h b Source #
Cast the type of the hashed data.
The Hash
type has a phantom type parameter to indicate what type the
hash is of. It is sometimes necessary to fake this and hash a value of one
type and use it where as hash of a different type is expected.
hashToBytes :: Hash h a -> ByteString Source #
The representation of the hash as bytes.
:: forall h a. HashAlgorithm h | |
=> ByteString | It must have an exact length, as given by |
-> Maybe (Hash h a) |
Make a hash from it bytes representation.
hashToBytesShort :: Hash h a -> ShortByteString Source #
The representation of the hash as bytes, as a ShortByteString
.
:: forall h a. HashAlgorithm h | |
=> ShortByteString | It must be a buffer of exact length, as given by |
-> Maybe (Hash h a) |
Make a hash from it bytes representation, as a ShortByteString
.
hashFromOffsetBytesShort Source #
:: forall h a. HashAlgorithm h | |
=> ShortByteString | It must be a buffer that contains at least |
-> Int | Offset in number of bytes |
-> Maybe (Hash h a) |
Just like hashFromBytesShort
, but allows using a region of a ShortByteString
.
hashToPackedBytes :: Hash h a -> PackedBytes (SizeHash h) Source #
O(1) - Get the underlying hash representation
hashFromPackedBytes :: PackedBytes (SizeHash h) -> Hash h a Source #
O(1) - Construct hash from the underlying representation
Rendering and parsing
hashToBytesAsHex :: Hash h a -> ByteString Source #
Convert the hash to hex encoding, as ByteString
.
hashFromBytesAsHex :: HashAlgorithm h => ByteString -> Maybe (Hash h a) Source #
Make a hash from hex-encoded ByteString
representation.
This can fail for the same reason as hashFromBytes
, or because the input
is invalid hex. The whole byte string must be valid hex, not just a prefix.
hashFromTextAsHex :: HashAlgorithm h => Text -> Maybe (Hash h a) Source #
Make a hash from hex-encoded Text
representation.
This can fail for the same reason as hashFromBytes
, or because the input
is invalid hex. The whole byte string must be valid hex, not just a prefix.
hashFromStringAsHex :: HashAlgorithm h => String -> Maybe (Hash h a) Source #
Make a hash from hex-encoded String
representation.
This can fail for the same reason as hashFromBytes
, or because the input
is invalid hex. The whole byte string must be valid hex, not just a prefix.
Other operations
Deprecated
hash :: forall h a. (HashAlgorithm h, ToCBOR a) => a -> Hash h a Source #
Deprecated: Use hashWith or hashWithSerialiser
hashRaw :: forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a Source #
Deprecated: Use hashWith
getHash :: Hash h a -> ByteString Source #
Deprecated: Use hashToBytes
getHashBytesAsHex :: Hash h a -> ByteString Source #
Deprecated: Use hashToBytesAsHex