{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Api.DRepMetadata
(
DRepMetadata (..)
, hashDRepMetadata
, AsType (..)
, Hash (..)
)
where
import Cardano.Api.Eras
import Cardano.Api.Hash
import Cardano.Api.HasTypeProxy
import Cardano.Api.Keys.Byron
import Cardano.Api.Keys.Praos
import Cardano.Api.Script
import Cardano.Api.SerialiseRaw
import qualified Cardano.Crypto.Hash.Class as Crypto
import Cardano.Ledger.Crypto (StandardCrypto)
import qualified Cardano.Ledger.Keys as Shelley
import Data.ByteString (ByteString)
import Data.Either.Combinators (maybeToRight)
newtype DRepMetadata = DRepMetadata
{ DRepMetadata -> ByteString
unDRepMetadata :: ByteString
}
deriving (DRepMetadata -> DRepMetadata -> Bool
(DRepMetadata -> DRepMetadata -> Bool)
-> (DRepMetadata -> DRepMetadata -> Bool) -> Eq DRepMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRepMetadata -> DRepMetadata -> Bool
== :: DRepMetadata -> DRepMetadata -> Bool
$c/= :: DRepMetadata -> DRepMetadata -> Bool
/= :: DRepMetadata -> DRepMetadata -> Bool
Eq, Int -> DRepMetadata -> ShowS
[DRepMetadata] -> ShowS
DRepMetadata -> String
(Int -> DRepMetadata -> ShowS)
-> (DRepMetadata -> String)
-> ([DRepMetadata] -> ShowS)
-> Show DRepMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepMetadata -> ShowS
showsPrec :: Int -> DRepMetadata -> ShowS
$cshow :: DRepMetadata -> String
show :: DRepMetadata -> String
$cshowList :: [DRepMetadata] -> ShowS
showList :: [DRepMetadata] -> ShowS
Show)
newtype instance Hash DRepMetadata = DRepMetadataHash (Shelley.Hash StandardCrypto ByteString)
deriving (Hash DRepMetadata -> Hash DRepMetadata -> Bool
(Hash DRepMetadata -> Hash DRepMetadata -> Bool)
-> (Hash DRepMetadata -> Hash DRepMetadata -> Bool)
-> Eq (Hash DRepMetadata)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash DRepMetadata -> Hash DRepMetadata -> Bool
== :: Hash DRepMetadata -> Hash DRepMetadata -> Bool
$c/= :: Hash DRepMetadata -> Hash DRepMetadata -> Bool
/= :: Hash DRepMetadata -> Hash DRepMetadata -> Bool
Eq, Int -> Hash DRepMetadata -> ShowS
[Hash DRepMetadata] -> ShowS
Hash DRepMetadata -> String
(Int -> Hash DRepMetadata -> ShowS)
-> (Hash DRepMetadata -> String)
-> ([Hash DRepMetadata] -> ShowS)
-> Show (Hash DRepMetadata)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash DRepMetadata -> ShowS
showsPrec :: Int -> Hash DRepMetadata -> ShowS
$cshow :: Hash DRepMetadata -> String
show :: Hash DRepMetadata -> String
$cshowList :: [Hash DRepMetadata] -> ShowS
showList :: [Hash DRepMetadata] -> ShowS
Show)
instance HasTypeProxy DRepMetadata where
data AsType DRepMetadata = AsDRepMetadata
proxyToAsType :: Proxy DRepMetadata -> AsType DRepMetadata
proxyToAsType :: Proxy DRepMetadata -> AsType DRepMetadata
proxyToAsType Proxy DRepMetadata
_ = AsType DRepMetadata
AsDRepMetadata
instance SerialiseAsRawBytes (Hash DRepMetadata) where
serialiseToRawBytes :: Hash DRepMetadata -> ByteString
serialiseToRawBytes :: Hash DRepMetadata -> ByteString
serialiseToRawBytes (DRepMetadataHash Hash StandardCrypto ByteString
h) = Hash Blake2b_256 ByteString -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash Blake2b_256 ByteString
Hash StandardCrypto ByteString
h
deserialiseFromRawBytes
:: AsType (Hash DRepMetadata) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepMetadata)
deserialiseFromRawBytes :: AsType (Hash DRepMetadata)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash DRepMetadata)
deserialiseFromRawBytes (AsHash AsType DRepMetadata
R:AsTypeDRepMetadata
AsDRepMetadata) ByteString
bs =
SerialiseAsRawBytesError
-> Maybe (Hash DRepMetadata)
-> Either SerialiseAsRawBytesError (Hash DRepMetadata)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash DRepMetadata") (Maybe (Hash DRepMetadata)
-> Either SerialiseAsRawBytesError (Hash DRepMetadata))
-> Maybe (Hash DRepMetadata)
-> Either SerialiseAsRawBytesError (Hash DRepMetadata)
forall a b. (a -> b) -> a -> b
$
Hash Blake2b_256 ByteString -> Hash DRepMetadata
Hash StandardCrypto ByteString -> Hash DRepMetadata
DRepMetadataHash (Hash Blake2b_256 ByteString -> Hash DRepMetadata)
-> Maybe (Hash Blake2b_256 ByteString) -> Maybe (Hash DRepMetadata)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_256 ByteString)
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
hashDRepMetadata
:: ByteString
-> (DRepMetadata, Hash DRepMetadata)
hashDRepMetadata :: ByteString -> (DRepMetadata, Hash DRepMetadata)
hashDRepMetadata ByteString
bs =
let md :: DRepMetadata
md = ByteString -> DRepMetadata
DRepMetadata ByteString
bs
mdh :: Hash DRepMetadata
mdh = Hash StandardCrypto ByteString -> Hash DRepMetadata
DRepMetadataHash ((ByteString -> ByteString)
-> ByteString -> Hash Blake2b_256 ByteString
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith ByteString -> ByteString
forall a. a -> a
id ByteString
bs)
in (DRepMetadata
md, Hash DRepMetadata
mdh)