cardano-crypto-class-2.0.0.0.0.0.0.2: Type classes abstracting over cryptography primitives for Cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Crypto.Hash.Class

Description

Abstract hashing functionality.

Synopsis

Documentation

class (KnownNat (SizeHash h), Typeable h) => HashAlgorithm h where Source #

Associated Types

type SizeHash h :: Nat Source #

Size of hash digest

Methods

hashAlgorithmName :: proxy h -> String Source #

digest :: proxy h -> ByteString -> ByteString Source #

Instances

Instances details
HashAlgorithm Blake2b_224 Source # 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_224 :: Nat Source #

HashAlgorithm Blake2b_256 Source # 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_256 :: Nat Source #

HashAlgorithm Keccak256 Source # 
Instance details

Defined in Cardano.Crypto.Hash.Keccak256

Associated Types

type SizeHash Keccak256 :: Nat Source #

HashAlgorithm NeverHash Source # 
Instance details

Defined in Cardano.Crypto.Hash.NeverUsed

Associated Types

type SizeHash NeverHash :: Nat Source #

HashAlgorithm SHA256 Source # 
Instance details

Defined in Cardano.Crypto.Hash.SHA256

Associated Types

type SizeHash SHA256 :: Nat Source #

HashAlgorithm SHA3_256 Source # 
Instance details

Defined in Cardano.Crypto.Hash.SHA3_256

Associated Types

type SizeHash SHA3_256 :: Nat Source #

(KnownNat n, CmpNat n 33 ~ 'LT) => HashAlgorithm (Blake2bPrefix n) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Short

Associated Types

type SizeHash (Blake2bPrefix n) :: Nat Source #

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

Instances details
Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString Source #

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString Source #

toConstr :: ByteString -> Constr Source #

dataTypeOf :: ByteString -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) Source #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString Source #

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal

Associated Types

type Item ByteString Source #

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

FromCBOR ByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

ToCBOR ByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

SignableRepresentation ByteString Source # 
Instance details

Defined in Cardano.Crypto.Util

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () Source #

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

HeapWords ByteString 
Instance details

Defined in Cardano.HeapWords

ByteArray ByteString 
Instance details

Defined in Data.ByteArray.Types

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, ByteString) Source #

ByteArrayAccess ByteString 
Instance details

Defined in Data.ByteArray.Types

NoThunks ByteString

Instance for string bytestrings

Strict bytestrings shouldn't contain any thunks, but could, due to https://gitlab.haskell.org/ghc/ghc/issues/17290. However, such thunks can't retain any data that they shouldn't, and so it's safe to ignore such thunks.

Instance details

Defined in NoThunks.Class

Serialise ByteString

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

Lift ByteString

Since: bytestring-0.11.2.0

Instance details

Defined in Data.ByteString.Internal

Methods

lift :: Quote m => ByteString -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString Source #

Decoded (Annotated b ByteString) 
Instance details

Defined in Cardano.Binary.Annotated

Associated Types

type BaseType (Annotated b ByteString) Source #

type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type Item ByteString 
Instance details

Defined in Data.ByteString.Internal

type BaseType (Annotated b ByteString) 
Instance details

Defined in Cardano.Binary.Annotated

data Hash h a where Source #

Bundled Patterns

pattern UnsafeHash :: forall h a. HashAlgorithm h => ShortByteString -> Hash h a 

Instances

Instances details
HashAlgorithm h => IsString (Q (TExp (Hash h a))) Source #

This instance is meant to be used with TemplateHaskell

>>> import Cardano.Crypto.Hash.Class (Hash)
>>> import Cardano.Crypto.Hash.Short (ShortHash)
>>> :set -XTemplateHaskell
>>> :set -XOverloadedStrings
>>> let hash = $$("0xBADC0FFEE0DDF00D") :: Hash ShortHash ()
>>> print hash
"badc0ffee0ddf00d"
>>> let hash = $$("0123456789abcdef") :: Hash ShortHash ()
>>> print hash
"0123456789abcdef"
>>> let hash = $$("deadbeef") :: Hash ShortHash ()
<interactive>:5:15: error:
    • <Hash blake2b_prefix_8>: Expected in decoded form to be: 8 bytes, but got: 4
    • In the Template Haskell splice $$("deadbeef")
      In the expression: $$("deadbeef") :: Hash ShortHash ()
      In an equation for ‘hash’:
          hash = $$("deadbeef") :: Hash ShortHash ()
>>> let hash = $$("123") :: Hash ShortHash ()
<interactive>:6:15: error:
    • <Hash blake2b_prefix_8>: Malformed hex: invalid bytestring size
    • In the Template Haskell splice $$("123")
      In the expression: $$("123") :: Hash ShortHash ()
      In an equation for ‘hash’: hash = $$("123") :: Hash ShortHash ()
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromString :: String -> Q (TExp (Hash h a)) Source #

HashAlgorithm h => FromJSON (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h => FromJSONKey (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h => ToJSON (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h => ToJSONKey (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h => IsString (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromString :: String -> Hash h a Source #

Generic (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Associated Types

type Rep (Hash h a) :: Type -> Type Source #

Methods

from :: Hash h a -> Rep (Hash h a) x Source #

to :: Rep (Hash h a) x -> Hash h a Source #

HashAlgorithm h => Read (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Show (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

showsPrec :: Int -> Hash h a -> ShowS Source #

show :: Hash h a -> String Source #

showList :: [Hash h a] -> ShowS Source #

(HashAlgorithm h, Typeable a) => FromCBOR (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromCBOR :: Decoder s (Hash h a) Source #

label :: Proxy (Hash h a) -> Text Source #

(HashAlgorithm h, Typeable a) => ToCBOR (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toCBOR :: Hash h a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash h a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash h a] -> Size Source #

NFData (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

rnf :: Hash h a -> () Source #

Eq (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

(==) :: Hash h a -> Hash h a -> Bool Source #

(/=) :: Hash h a -> Hash h a -> Bool Source #

Ord (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

compare :: Hash h a -> Hash h a -> Ordering Source #

(<) :: Hash h a -> Hash h a -> Bool Source #

(<=) :: Hash h a -> Hash h a -> Bool Source #

(>) :: Hash h a -> Hash h a -> Bool Source #

(>=) :: Hash h a -> Hash h a -> Bool Source #

max :: Hash h a -> Hash h a -> Hash h a Source #

min :: Hash h a -> Hash h a -> Hash h a Source #

HeapWords (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

heapWords :: Hash h a -> Int Source #

NoThunks (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

type Rep (Hash h a) Source # 
Instance details

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 #

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.

hashFromBytes Source #

Arguments

:: forall h a. HashAlgorithm h 
=> ByteString

It must have an exact length, as given by sizeHash.

-> 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.

hashFromBytesShort Source #

Arguments

:: forall h a. HashAlgorithm h 
=> ShortByteString

It must be a buffer of exact length, as given by sizeHash.

-> Maybe (Hash h a) 

Make a hash from it bytes representation, as a ShortByteString.

hashFromOffsetBytesShort Source #

Arguments

:: forall h a. HashAlgorithm h 
=> ShortByteString

It must be a buffer that contains at least sizeHash many bytes staring at an offset.

-> 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.

hashToTextAsHex :: Hash h a -> Text Source #

Convert the hash to hex encoding, as Text.

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.

hashToStringAsHex :: Hash h a -> String Source #

Convert the hash to hex encoding, as String.

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

xor :: Hash h a -> Hash h a -> Hash h a Source #

XOR two hashes together

Deprecated

hash :: forall h a. (HashAlgorithm h, ToCBOR a) => a -> Hash h a Source #

Deprecated: Use hashWith or hashWithSerialiser

fromHash :: Hash h a -> Natural Source #

Deprecated: Use bytesToNatural . hashToBytes

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