cardano-crypto-class-2.0.0: Type classes abstracting over cryptography primitives for Cardano
Safe HaskellNone
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 #

Methods

hashAlgorithmName :: proxy h -> String Source #

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

Instances

Instances details
HashAlgorithm Blake2b_256 Source # 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_256 :: Nat Source #

HashAlgorithm Blake2b_224 Source # 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_224 :: Nat Source #

HashAlgorithm MD5 Source # 
Instance details

Defined in Cardano.Crypto.Hash.MD5

Associated Types

type SizeHash MD5 :: 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 (MD5Prefix n) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Short

Associated Types

type SizeHash (MD5Prefix n) :: Nat Source #

sizeHash :: forall h proxy. HashAlgorithm h => proxy h -> Word Source #

The size in bytes of the output of digest

data ByteString #

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

Associated Types

type Item ByteString #

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 #

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

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

ToCBOR ByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

FromCBOR ByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

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

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString

SignableRepresentation ByteString Source # 
Instance details

Defined in Cardano.Crypto.Util

Decoded (Annotated b ByteString) 
Instance details

Defined in Cardano.Binary.Annotated

Associated Types

type BaseType (Annotated b ByteString) Source #

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal

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 ChunkElem ByteString = Word8
type BaseType (Annotated b ByteString) 
Instance details

Defined in Cardano.Binary.Annotated

newtype Hash h a Source #

Instances

Instances details
Eq (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

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

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

Ord (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

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

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

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

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

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

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

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

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

Defined in Cardano.Crypto.Hash.Class

Methods

readsPrec :: Int -> ReadS (Hash h a) #

readList :: ReadS [Hash h a] #

readPrec :: ReadPrec (Hash h a) #

readListPrec :: ReadPrec [Hash h a] #

Show (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

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

show :: Hash h a -> String #

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

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

Defined in Cardano.Crypto.Hash.Class

Methods

fromString :: String -> Hash h a #

Generic (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Associated Types

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

Methods

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

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

ToJSON (Hash crypto a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toJSON :: Hash crypto a -> Value Source #

toEncoding :: Hash crypto a -> Encoding Source #

toJSONList :: [Hash crypto a] -> Value Source #

toEncodingList :: [Hash crypto a] -> Encoding Source #

ToJSONKey (Hash crypto a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

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

Defined in Cardano.Crypto.Hash.Class

Methods

parseJSON :: Value -> Parser (Hash crypto a) Source #

parseJSONList :: Value -> Parser [Hash crypto a] Source #

HashAlgorithm crypto => FromJSONKey (Hash crypto 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

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 #

(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 #

NFData (Hash h a) Source # 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

rnf :: Hash h a -> () #

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-8Wg6S5FD924IEUDdpkXXc" 'True) (C1 ('MetaCons "UnsafeHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

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 :: forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a) Source #

Make a hash from it bytes representation.

It must be a a bytestring of the correct length, as given by sizeHash.

hashToBytesShort :: Hash h a -> ShortByteString Source #

The representation of the hash as bytes, as a ShortByteString.

hashFromBytesShort :: forall h a. HashAlgorithm h => ShortByteString -> Maybe (Hash h a) Source #

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

It must be a a bytestring of the correct length, as given by sizeHash.

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 TODO: fully deprecate this, or rename it and make it efficient.

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