cardano-crypto-class-2.0.0.0.1: Type classes abstracting over cryptography primitives for Cardano
Safe Haskell None
Language Haskell2010

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

Instances

Instances details
HashAlgorithm SHA3_256 Source #
Instance details

Defined in Cardano.Crypto.Hash.SHA3_256

HashAlgorithm NeverHash Source #
Instance details

Defined in Cardano.Crypto.Hash.NeverUsed

HashAlgorithm Keccak256 Source #
Instance details

Defined in Cardano.Crypto.Hash.Keccak256

HashAlgorithm Blake2b_256 Source #
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

HashAlgorithm Blake2b_224 Source #
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

HashAlgorithm SHA256 Source #
Instance details

Defined in Cardano.Crypto.Hash.SHA256

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

Defined in Cardano.Crypto.Hash.Short

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
IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal

Eq ByteString
Instance details

Defined in Data.ByteString.Internal

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 #

Ord ByteString
Instance details

Defined in Data.ByteString.Internal

Read ByteString
Instance details

Defined in Data.ByteString.Internal

Show ByteString
Instance details

Defined in Data.ByteString.Internal

IsString ByteString

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

Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString
Instance details

Defined in Data.ByteString.Internal

Hashable ByteString
Instance details

Defined in Data.Hashable.Class

Chunk ByteString
Instance details

Defined in Data.Attoparsec.Internal.Types

ToCBOR ByteString
Instance details

Defined in Cardano.Binary.ToCBOR

FromCBOR ByteString
Instance details

Defined in Cardano.Binary.FromCBOR

HeapWords ByteString
Instance details

Defined in Cardano.Prelude.HeapWords

NFData ByteString
Instance details

Defined in Data.ByteString.Internal

ByteArray ByteString
Instance details

Defined in Data.ByteArray.Types

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

SignableRepresentation ByteString Source #
Instance details

Defined in Cardano.Crypto.Util

Decoded ( Annotated b ByteString )
Instance details

Defined in Cardano.Binary.Annotated

type State ByteString
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type ChunkElem ByteString
Instance details

Defined in Data.Attoparsec.Internal.Types

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
Eq ( Hash h a) Source #
Instance details

Defined in Cardano.Crypto.Hash.Class

Ord ( Hash h a) Source #
Instance details

Defined in Cardano.Crypto.Hash.Class

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

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

Defined in Cardano.Crypto.Hash.Class

Generic ( Hash h a) Source #
Instance details

Defined in Cardano.Crypto.Hash.Class

Associated Types

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

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 => 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, Typeable a) => ToCBOR ( Hash h a) Source #
Instance details

Defined in Cardano.Crypto.Hash.Class

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

Defined in Cardano.Crypto.Hash.Class

HeapWords ( Hash h a) Source #
Instance details

Defined in Cardano.Crypto.Hash.Class

NFData ( Hash h a) Source #
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

rnf :: Hash h a -> () 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.1-5PqST7yhL1v7PBV5z4tsb9" ' 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