{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module Cardano.Crypto.Hashing
(
AbstractHash,
HashAlgorithm,
abstractHash,
unsafeAbstractHash,
abstractHashFromDigest,
abstractHashFromBytes,
unsafeAbstractHashFromBytes,
abstractHashToBytes,
unsafeAbstractHashFromShort,
abstractHashToShort,
decodeAbstractHash,
Hash,
hash,
hashDecoded,
hashRaw,
serializeCborHash,
hashFromBytes,
unsafeHashFromBytes,
hashToBytes,
decodeHash,
hashHexF,
mediumHashF,
shortHashF,
)
where
import Cardano.Binary
( Decoded (..),
DecoderError (..),
FromCBOR (..),
Raw,
ToCBOR (..),
serialize,
withWordSize,
)
import Cardano.Prelude
import Crypto.Hash (Blake2b_256, Digest, HashAlgorithm, hashDigestSize)
import qualified Crypto.Hash as Hash
import Data.Aeson
( FromJSON (..),
FromJSONKey (..),
FromJSONKeyFunction (..),
ToJSON (..),
ToJSONKey (..),
)
import Data.Aeson.Types (toJSONKeyText)
import qualified Data.ByteArray as ByteArray
import qualified Data.ByteArray.Encoding as ByteArray
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Char8 as BSC
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Short as SBS
import qualified Data.Text.Encoding as T
import Formatting (Format, bprint, build, fitLeft, later, sformat, (%.))
import qualified Formatting.Buildable as B (Buildable (..))
import NoThunks.Class (NoThunks (..))
import qualified Prelude
newtype AbstractHash algo a = AbstractHash SBS.ShortByteString
deriving (AbstractHash algo a -> AbstractHash algo a -> Bool
(AbstractHash algo a -> AbstractHash algo a -> Bool)
-> (AbstractHash algo a -> AbstractHash algo a -> Bool)
-> Eq (AbstractHash algo a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
/= :: AbstractHash algo a -> AbstractHash algo a -> Bool
$c/= :: forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
== :: AbstractHash algo a -> AbstractHash algo a -> Bool
$c== :: forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
Eq, Eq (AbstractHash algo a)
Eq (AbstractHash algo a)
-> (AbstractHash algo a -> AbstractHash algo a -> Ordering)
-> (AbstractHash algo a -> AbstractHash algo a -> Bool)
-> (AbstractHash algo a -> AbstractHash algo a -> Bool)
-> (AbstractHash algo a -> AbstractHash algo a -> Bool)
-> (AbstractHash algo a -> AbstractHash algo a -> Bool)
-> (AbstractHash algo a
-> AbstractHash algo a -> AbstractHash algo a)
-> (AbstractHash algo a
-> AbstractHash algo a -> AbstractHash algo a)
-> Ord (AbstractHash algo a)
AbstractHash algo a -> AbstractHash algo a -> Bool
AbstractHash algo a -> AbstractHash algo a -> Ordering
AbstractHash algo a -> AbstractHash algo a -> AbstractHash algo a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall algo a. Eq (AbstractHash algo a)
forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
forall algo a.
AbstractHash algo a -> AbstractHash algo a -> Ordering
forall algo a.
AbstractHash algo a -> AbstractHash algo a -> AbstractHash algo a
min :: AbstractHash algo a -> AbstractHash algo a -> AbstractHash algo a
$cmin :: forall algo a.
AbstractHash algo a -> AbstractHash algo a -> AbstractHash algo a
max :: AbstractHash algo a -> AbstractHash algo a -> AbstractHash algo a
$cmax :: forall algo a.
AbstractHash algo a -> AbstractHash algo a -> AbstractHash algo a
>= :: AbstractHash algo a -> AbstractHash algo a -> Bool
$c>= :: forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
> :: AbstractHash algo a -> AbstractHash algo a -> Bool
$c> :: forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
<= :: AbstractHash algo a -> AbstractHash algo a -> Bool
$c<= :: forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
< :: AbstractHash algo a -> AbstractHash algo a -> Bool
$c< :: forall algo a. AbstractHash algo a -> AbstractHash algo a -> Bool
compare :: AbstractHash algo a -> AbstractHash algo a -> Ordering
$ccompare :: forall algo a.
AbstractHash algo a -> AbstractHash algo a -> Ordering
$cp1Ord :: forall algo a. Eq (AbstractHash algo a)
Ord, (forall x. AbstractHash algo a -> Rep (AbstractHash algo a) x)
-> (forall x. Rep (AbstractHash algo a) x -> AbstractHash algo a)
-> Generic (AbstractHash algo a)
forall x. Rep (AbstractHash algo a) x -> AbstractHash algo a
forall x. AbstractHash algo a -> Rep (AbstractHash algo a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall algo a x. Rep (AbstractHash algo a) x -> AbstractHash algo a
forall algo a x. AbstractHash algo a -> Rep (AbstractHash algo a) x
$cto :: forall algo a x. Rep (AbstractHash algo a) x -> AbstractHash algo a
$cfrom :: forall algo a x. AbstractHash algo a -> Rep (AbstractHash algo a) x
Generic, AbstractHash algo a -> ()
(AbstractHash algo a -> ()) -> NFData (AbstractHash algo a)
forall a. (a -> ()) -> NFData a
forall algo a. AbstractHash algo a -> ()
rnf :: AbstractHash algo a -> ()
$crnf :: forall algo a. AbstractHash algo a -> ()
NFData, Context -> AbstractHash algo a -> IO (Maybe ThunkInfo)
Proxy (AbstractHash algo a) -> String
(Context -> AbstractHash algo a -> IO (Maybe ThunkInfo))
-> (Context -> AbstractHash algo a -> IO (Maybe ThunkInfo))
-> (Proxy (AbstractHash algo a) -> String)
-> NoThunks (AbstractHash algo a)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall algo a.
Context -> AbstractHash algo a -> IO (Maybe ThunkInfo)
forall algo a. Proxy (AbstractHash algo a) -> String
showTypeOf :: Proxy (AbstractHash algo a) -> String
$cshowTypeOf :: forall algo a. Proxy (AbstractHash algo a) -> String
wNoThunks :: Context -> AbstractHash algo a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall algo a.
Context -> AbstractHash algo a -> IO (Maybe ThunkInfo)
noThunks :: Context -> AbstractHash algo a -> IO (Maybe ThunkInfo)
$cnoThunks :: forall algo a.
Context -> AbstractHash algo a -> IO (Maybe ThunkInfo)
NoThunks)
instance Show (AbstractHash algo a) where
show :: AbstractHash algo a -> String
show (AbstractHash ShortByteString
h) =
ByteString -> String
BSC.unpack
(ByteString -> String)
-> (ShortByteString -> ByteString) -> ShortByteString -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
ByteArray.convertToBase Base
ByteArray.Base16
(ByteString -> ByteString)
-> (ShortByteString -> ByteString) -> ShortByteString -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ShortByteString -> ByteString
SBS.fromShort
(ShortByteString -> String) -> ShortByteString -> String
forall a b. (a -> b) -> a -> b
$ ShortByteString
h
instance HashAlgorithm algo => Read (AbstractHash algo a) where
readsPrec :: Int -> ReadS (AbstractHash algo a)
readsPrec Int
_ String
s = case ByteString -> Either String ByteString
B16.decode (Text -> ByteString
T.encodeUtf8 (String -> Text
forall a b. ConvertText a b => a -> b
toS String
s)) of
Left String
_ -> []
Right ByteString
bs -> case ByteString -> Maybe (AbstractHash algo a)
forall algo a.
HashAlgorithm algo =>
ByteString -> Maybe (AbstractHash algo a)
abstractHashFromBytes ByteString
bs of
Maybe (AbstractHash algo a)
Nothing -> []
Just AbstractHash algo a
h -> [(AbstractHash algo a
h, String
"")]
instance B.Buildable (AbstractHash algo a) where
build :: AbstractHash algo a -> Builder
build = Format Builder (AbstractHash algo a -> Builder)
-> AbstractHash algo a -> Builder
forall a. Format Builder a -> a
bprint Format Builder (AbstractHash algo a -> Builder)
forall r algo a. Format r (AbstractHash algo a -> r)
mediumHashF
instance ToJSON (AbstractHash algo a) where
toJSON :: AbstractHash algo a -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (AbstractHash algo a -> Text) -> AbstractHash algo a -> Value
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Text (AbstractHash algo a -> Text)
-> AbstractHash algo a -> Text
forall a. Format Text a -> a
sformat Format Text (AbstractHash algo a -> Text)
forall r algo a. Format r (AbstractHash algo a -> r)
hashHexF
instance HashAlgorithm algo => FromJSON (AbstractHash algo a) where
parseJSON :: Value -> Parser (AbstractHash algo a)
parseJSON = Either String (AbstractHash algo a) -> Parser (AbstractHash algo a)
forall e a. Buildable e => Either e a -> Parser a
toAesonError (Either String (AbstractHash algo a)
-> Parser (AbstractHash algo a))
-> (String -> Either String (AbstractHash algo a))
-> String
-> Parser (AbstractHash algo a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Either String (AbstractHash algo a)
forall a. Read a => String -> Either String a
readEither (String -> Parser (AbstractHash algo a))
-> (Value -> Parser String)
-> Value
-> Parser (AbstractHash algo a)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser String
forall a. FromJSON a => Value -> Parser a
parseJSON
instance
(HashAlgorithm algo, FromJSON (AbstractHash algo a)) =>
FromJSONKey (AbstractHash algo a)
where
fromJSONKey :: FromJSONKeyFunction (AbstractHash algo a)
fromJSONKey = (Text -> Parser (AbstractHash algo a))
-> FromJSONKeyFunction (AbstractHash algo a)
forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser (Either Text (AbstractHash algo a) -> Parser (AbstractHash algo a)
forall e a. Buildable e => Either e a -> Parser a
toAesonError (Either Text (AbstractHash algo a) -> Parser (AbstractHash algo a))
-> (Text -> Either Text (AbstractHash algo a))
-> Text
-> Parser (AbstractHash algo a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> Either Text (AbstractHash algo a)
forall algo a.
HashAlgorithm algo =>
Text -> Either Text (AbstractHash algo a)
decodeAbstractHash)
instance ToJSONKey (AbstractHash algo a) where
toJSONKey :: ToJSONKeyFunction (AbstractHash algo a)
toJSONKey = (AbstractHash algo a -> Text)
-> ToJSONKeyFunction (AbstractHash algo a)
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText (Format Text (AbstractHash algo a -> Text)
-> AbstractHash algo a -> Text
forall a. Format Text a -> a
sformat Format Text (AbstractHash algo a -> Text)
forall r algo a. Format r (AbstractHash algo a -> r)
hashHexF)
instance (Typeable algo, Typeable a, HashAlgorithm algo) => ToCBOR (AbstractHash algo a) where
toCBOR :: AbstractHash algo a -> Encoding
toCBOR (AbstractHash ShortByteString
h) = ShortByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR ShortByteString
h
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (AbstractHash algo a) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ Proxy (AbstractHash algo a)
_ =
let realSz :: Int
realSz = algo -> Int
forall a. HashAlgorithm a => a -> Int
hashDigestSize (Text -> algo
forall a. HasCallStack => Text -> a
panic Text
"unused, I hope!" :: algo)
in Integer -> Size
forall a. Num a => Integer -> a
fromInteger (Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Int
forall s a. (Integral s, Integral a) => s -> a
withWordSize Int
realSz Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
realSz))
instance
(Typeable algo, Typeable a, HashAlgorithm algo) =>
FromCBOR (AbstractHash algo a)
where
fromCBOR :: Decoder s (AbstractHash algo a)
fromCBOR = do
ShortByteString
bs <- forall s. FromCBOR ShortByteString => Decoder s ShortByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR @SBS.ShortByteString
Bool -> Decoder s () -> Decoder s ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ShortByteString -> Int
SBS.length ShortByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
expectedSize) (Decoder s () -> Decoder s ()) -> Decoder s () -> Decoder s ()
forall a b. (a -> b) -> a -> b
$
DecoderError -> Decoder s ()
forall e s a. Buildable e => e -> Decoder s a
cborError (DecoderError -> Decoder s ()) -> DecoderError -> Decoder s ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> DecoderError
DecoderErrorCustom Text
"AbstractHash" Text
"Bytes not expected length"
AbstractHash algo a -> Decoder s (AbstractHash algo a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ShortByteString -> AbstractHash algo a
forall algo a. ShortByteString -> AbstractHash algo a
AbstractHash ShortByteString
bs)
where
expectedSize :: Int
expectedSize = algo -> Int
forall a. HashAlgorithm a => a -> Int
hashDigestSize (algo
forall a. HasCallStack => a
Prelude.undefined :: algo)
instance HeapWords (AbstractHash algo a) where
heapWords :: AbstractHash algo a -> Int
heapWords AbstractHash algo a
_ =
Int
8
decodeAbstractHash ::
HashAlgorithm algo => Text -> Either Text (AbstractHash algo a)
decodeAbstractHash :: Text -> Either Text (AbstractHash algo a)
decodeAbstractHash Text
prettyHash = do
ByteString
bytes <- (String -> Text)
-> Either String ByteString -> Either Text ByteString
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Format Text (String -> Text) -> String -> Text
forall a. Format Text a -> a
sformat Format Text (String -> Text)
forall a r. Buildable a => Format r (a -> r)
build) (Either String ByteString -> Either Text ByteString)
-> Either String ByteString -> Either Text ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String ByteString
B16.decode (Text -> ByteString
T.encodeUtf8 Text
prettyHash)
case ByteString -> Maybe (AbstractHash algo a)
forall algo a.
HashAlgorithm algo =>
ByteString -> Maybe (AbstractHash algo a)
abstractHashFromBytes ByteString
bytes of
Maybe (AbstractHash algo a)
Nothing ->
Text -> Either Text (AbstractHash algo a)
forall a b. a -> Either a b
Left
( Text
"decodeAbstractHash: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"can't convert bytes to hash,"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" the value was "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall a b. ConvertText a b => a -> b
toS Text
prettyHash
)
Just AbstractHash algo a
h -> AbstractHash algo a -> Either Text (AbstractHash algo a)
forall (m :: * -> *) a. Monad m => a -> m a
return AbstractHash algo a
h
abstractHash :: (HashAlgorithm algo, ToCBOR a) => a -> AbstractHash algo a
abstractHash :: a -> AbstractHash algo a
abstractHash = LByteString -> AbstractHash algo a
forall algo a.
HashAlgorithm algo =>
LByteString -> AbstractHash algo a
unsafeAbstractHash (LByteString -> AbstractHash algo a)
-> (a -> LByteString) -> a -> AbstractHash algo a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> LByteString
forall a. ToCBOR a => a -> LByteString
serialize
unsafeAbstractHash :: HashAlgorithm algo => LByteString -> AbstractHash algo a
unsafeAbstractHash :: LByteString -> AbstractHash algo a
unsafeAbstractHash = Digest algo -> AbstractHash algo a
forall algo a. Digest algo -> AbstractHash algo a
abstractHashFromDigest (Digest algo -> AbstractHash algo a)
-> (LByteString -> Digest algo)
-> LByteString
-> AbstractHash algo a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. LByteString -> Digest algo
forall a. HashAlgorithm a => LByteString -> Digest a
Hash.hashlazy
abstractHashFromDigest :: Digest algo -> AbstractHash algo a
abstractHashFromDigest :: Digest algo -> AbstractHash algo a
abstractHashFromDigest = ShortByteString -> AbstractHash algo a
forall algo a. ShortByteString -> AbstractHash algo a
AbstractHash (ShortByteString -> AbstractHash algo a)
-> (Digest algo -> ShortByteString)
-> Digest algo
-> AbstractHash algo a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ShortByteString
SBS.toShort (ByteString -> ShortByteString)
-> (Digest algo -> ByteString) -> Digest algo -> ShortByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Digest algo -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
ByteArray.convert
abstractHashFromBytes ::
forall algo a.
HashAlgorithm algo =>
ByteString ->
Maybe (AbstractHash algo a)
abstractHashFromBytes :: ByteString -> Maybe (AbstractHash algo a)
abstractHashFromBytes ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
expectedSize = AbstractHash algo a -> Maybe (AbstractHash algo a)
forall a. a -> Maybe a
Just (ByteString -> AbstractHash algo a
forall algo a. ByteString -> AbstractHash algo a
unsafeAbstractHashFromBytes ByteString
bs)
| Bool
otherwise = Maybe (AbstractHash algo a)
forall a. Maybe a
Nothing
where
expectedSize :: Int
expectedSize = algo -> Int
forall a. HashAlgorithm a => a -> Int
hashDigestSize (algo
forall a. HasCallStack => a
Prelude.undefined :: algo)
unsafeAbstractHashFromBytes :: ByteString -> AbstractHash algo a
unsafeAbstractHashFromBytes :: ByteString -> AbstractHash algo a
unsafeAbstractHashFromBytes = ShortByteString -> AbstractHash algo a
forall algo a. ShortByteString -> AbstractHash algo a
AbstractHash (ShortByteString -> AbstractHash algo a)
-> (ByteString -> ShortByteString)
-> ByteString
-> AbstractHash algo a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ShortByteString
SBS.toShort
abstractHashToBytes :: AbstractHash algo a -> ByteString
abstractHashToBytes :: AbstractHash algo a -> ByteString
abstractHashToBytes (AbstractHash ShortByteString
h) = ShortByteString -> ByteString
SBS.fromShort ShortByteString
h
unsafeAbstractHashFromShort :: SBS.ShortByteString -> AbstractHash algo a
unsafeAbstractHashFromShort :: ShortByteString -> AbstractHash algo a
unsafeAbstractHashFromShort ShortByteString
h = (ShortByteString -> AbstractHash algo a
forall algo a. ShortByteString -> AbstractHash algo a
AbstractHash ShortByteString
h)
abstractHashToShort :: AbstractHash algo a -> SBS.ShortByteString
abstractHashToShort :: AbstractHash algo a -> ShortByteString
abstractHashToShort (AbstractHash ShortByteString
h) = ShortByteString
h
type Hash = AbstractHash Blake2b_256
{-# DEPRECATED hash "Use serializeCborHash or hash the annotation instead." #-}
hash :: ToCBOR a => a -> Hash a
hash :: a -> Hash a
hash = a -> Hash a
forall algo a.
(HashAlgorithm algo, ToCBOR a) =>
a -> AbstractHash algo a
abstractHash
serializeCborHash :: ToCBOR a => a -> Hash a
serializeCborHash :: a -> Hash a
serializeCborHash = a -> Hash a
forall algo a.
(HashAlgorithm algo, ToCBOR a) =>
a -> AbstractHash algo a
abstractHash
hashDecoded :: (Decoded t) => t -> Hash (BaseType t)
hashDecoded :: t -> Hash (BaseType t)
hashDecoded = LByteString -> Hash (BaseType t)
forall algo a.
HashAlgorithm algo =>
LByteString -> AbstractHash algo a
unsafeAbstractHash (LByteString -> Hash (BaseType t))
-> (t -> LByteString) -> t -> Hash (BaseType t)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> LByteString
LBS.fromStrict (ByteString -> LByteString)
-> (t -> ByteString) -> t -> LByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. t -> ByteString
forall t. Decoded t => t -> ByteString
recoverBytes
hashRaw :: LBS.ByteString -> Hash Raw
hashRaw :: LByteString -> Hash Raw
hashRaw = LByteString -> Hash Raw
forall algo a.
HashAlgorithm algo =>
LByteString -> AbstractHash algo a
unsafeAbstractHash
hashFromBytes :: ByteString -> Maybe (Hash a)
hashFromBytes :: ByteString -> Maybe (Hash a)
hashFromBytes = ByteString -> Maybe (Hash a)
forall algo a.
HashAlgorithm algo =>
ByteString -> Maybe (AbstractHash algo a)
abstractHashFromBytes
unsafeHashFromBytes :: ByteString -> Hash a
unsafeHashFromBytes :: ByteString -> Hash a
unsafeHashFromBytes = ByteString -> Hash a
forall algo a. ByteString -> AbstractHash algo a
unsafeAbstractHashFromBytes
hashToBytes :: AbstractHash algo a -> ByteString
hashToBytes :: AbstractHash algo a -> ByteString
hashToBytes = AbstractHash algo a -> ByteString
forall algo a. AbstractHash algo a -> ByteString
abstractHashToBytes
decodeHash :: Text -> Either Text (Hash a)
decodeHash :: Text -> Either Text (Hash a)
decodeHash = forall a.
HashAlgorithm Blake2b_256 =>
Text -> Either Text (AbstractHash Blake2b_256 a)
forall algo a.
HashAlgorithm algo =>
Text -> Either Text (AbstractHash algo a)
decodeAbstractHash @Blake2b_256
hashHexF :: Format r (AbstractHash algo a -> r)
hashHexF :: Format r (AbstractHash algo a -> r)
hashHexF = (AbstractHash algo a -> Builder)
-> Format r (AbstractHash algo a -> r)
forall a r. (a -> Builder) -> Format r (a -> r)
later ((AbstractHash algo a -> Builder)
-> Format r (AbstractHash algo a -> r))
-> (AbstractHash algo a -> Builder)
-> Format r (AbstractHash algo a -> r)
forall a b. (a -> b) -> a -> b
$ \AbstractHash algo a
h -> Text -> Builder
forall p. Buildable p => p -> Builder
B.build (AbstractHash algo a -> Text
forall a b. (Show a, ConvertText String b) => a -> b
show AbstractHash algo a
h :: Text)
mediumHashF :: Format r (AbstractHash algo a -> r)
mediumHashF :: Format r (AbstractHash algo a -> r)
mediumHashF = Int -> Format r (Builder -> r)
forall a r. Buildable a => Int -> Format r (a -> r)
fitLeft Int
16 Format r (Builder -> r)
-> Format r (AbstractHash algo a -> r)
-> Format r (AbstractHash algo a -> r)
forall r r' a.
Format r (Builder -> r') -> Format r' a -> Format r a
%. Format r (AbstractHash algo a -> r)
forall r algo a. Format r (AbstractHash algo a -> r)
hashHexF
shortHashF :: Format r (AbstractHash algo a -> r)
shortHashF :: Format r (AbstractHash algo a -> r)
shortHashF = Int -> Format r (Builder -> r)
forall a r. Buildable a => Int -> Format r (a -> r)
fitLeft Int
8 Format r (Builder -> r)
-> Format r (AbstractHash algo a -> r)
-> Format r (AbstractHash algo a -> r)
forall r r' a.
Format r (Builder -> r') -> Format r' a -> Format r a
%. Format r (AbstractHash algo a -> r)
forall r algo a. Format r (AbstractHash algo a -> r)
hashHexF