{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Bcc.Api.KeysSophie (
PaymentKey,
PaymentExtendedKey,
StakeKey,
StakeExtendedKey,
StakePoolKey,
GenesisKey,
GenesisExtendedKey,
GenesisDelegateKey,
GenesisDelegateExtendedKey,
GenesisVestedKey,
GenesisVestedExtendedKey,
GenesisVestedDelegateKey,
GenesisVestedDelegateExtendedKey,
GenesisUTxOKey,
VestedKey,
VestedExtendedKey,
VestedDelegateKey,
VestedDelegateExtendedKey,
VestedUTxOKey,
AsType(..),
VerificationKey(..),
SigningKey(..),
Hash(..),
) where
import Prelude
import Data.Aeson.Types (ToJSONKey (..), toJSONKeyText)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Maybe
import Data.String (IsString (..))
import qualified Bcc.Crypto.DSIGN.Class as Crypto
import qualified Bcc.Crypto.Hash.Class as Crypto
import qualified Bcc.Crypto.Seed as Crypto
import qualified Bcc.Crypto.Wallet as Crypto.HD
import qualified Bcc.Ledger.Crypto as Sophie (DSIGN)
import qualified Bcc.Ledger.Keys as Sophie
import Bcc.Ledger.Crypto (StandardCrypto)
import Bcc.Api.Hash
import Bcc.Api.HasTypeProxy
import Bcc.Api.Key
import Bcc.Api.SerialiseBech32
import Bcc.Api.SerialiseCBOR
import Bcc.Api.SerialiseJSON
import Bcc.Api.SerialiseRaw
import Bcc.Api.SerialiseTextEnvelope
import Bcc.Api.SerialiseUsing
data PaymentKey
instance HasTypeProxy PaymentKey where
data AsType PaymentKey = AsPaymentKey
proxyToAsType :: Proxy PaymentKey -> AsType PaymentKey
proxyToAsType Proxy PaymentKey
_ = AsType PaymentKey
AsPaymentKey
instance Key PaymentKey where
newtype VerificationKey PaymentKey =
PaymentVerificationKey (Sophie.VKey Sophie.Payment StandardCrypto)
deriving stock (VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
(VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool)
-> (VerificationKey PaymentKey
-> VerificationKey PaymentKey -> Bool)
-> Eq (VerificationKey PaymentKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
$c/= :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
== :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
$c== :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
Eq)
deriving (Int -> VerificationKey PaymentKey -> ShowS
[VerificationKey PaymentKey] -> ShowS
VerificationKey PaymentKey -> String
(Int -> VerificationKey PaymentKey -> ShowS)
-> (VerificationKey PaymentKey -> String)
-> ([VerificationKey PaymentKey] -> ShowS)
-> Show (VerificationKey PaymentKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey PaymentKey] -> ShowS
$cshowList :: [VerificationKey PaymentKey] -> ShowS
show :: VerificationKey PaymentKey -> String
$cshow :: VerificationKey PaymentKey -> String
showsPrec :: Int -> VerificationKey PaymentKey -> ShowS
$cshowsPrec :: Int -> VerificationKey PaymentKey -> ShowS
Show, String -> VerificationKey PaymentKey
(String -> VerificationKey PaymentKey)
-> IsString (VerificationKey PaymentKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey PaymentKey
$cfromString :: String -> VerificationKey PaymentKey
IsString) via UsingRawBytesHex (VerificationKey PaymentKey)
deriving newtype (Typeable (VerificationKey PaymentKey)
Typeable (VerificationKey PaymentKey)
-> (VerificationKey PaymentKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size)
-> ToCBOR (VerificationKey PaymentKey)
VerificationKey PaymentKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size
toCBOR :: VerificationKey PaymentKey -> Encoding
$ctoCBOR :: VerificationKey PaymentKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey PaymentKey)
ToCBOR, Typeable (VerificationKey PaymentKey)
Decoder s (VerificationKey PaymentKey)
Typeable (VerificationKey PaymentKey)
-> (forall s. Decoder s (VerificationKey PaymentKey))
-> (Proxy (VerificationKey PaymentKey) -> Text)
-> FromCBOR (VerificationKey PaymentKey)
Proxy (VerificationKey PaymentKey) -> Text
forall s. Decoder s (VerificationKey PaymentKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey PaymentKey) -> Text
$clabel :: Proxy (VerificationKey PaymentKey) -> Text
fromCBOR :: Decoder s (VerificationKey PaymentKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey PaymentKey)
$cp1FromCBOR :: Typeable (VerificationKey PaymentKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey PaymentKey)
HasTypeProxy (VerificationKey PaymentKey)
-> (VerificationKey PaymentKey -> ByteString)
-> (AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey))
-> SerialiseAsCBOR (VerificationKey PaymentKey)
AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey)
VerificationKey PaymentKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey)
serialiseToCBOR :: VerificationKey PaymentKey -> ByteString
$cserialiseToCBOR :: VerificationKey PaymentKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey PaymentKey)
SerialiseAsCBOR
newtype SigningKey PaymentKey =
PaymentSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey PaymentKey -> ShowS
[SigningKey PaymentKey] -> ShowS
SigningKey PaymentKey -> String
(Int -> SigningKey PaymentKey -> ShowS)
-> (SigningKey PaymentKey -> String)
-> ([SigningKey PaymentKey] -> ShowS)
-> Show (SigningKey PaymentKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey PaymentKey] -> ShowS
$cshowList :: [SigningKey PaymentKey] -> ShowS
show :: SigningKey PaymentKey -> String
$cshow :: SigningKey PaymentKey -> String
showsPrec :: Int -> SigningKey PaymentKey -> ShowS
$cshowsPrec :: Int -> SigningKey PaymentKey -> ShowS
Show, String -> SigningKey PaymentKey
(String -> SigningKey PaymentKey)
-> IsString (SigningKey PaymentKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey PaymentKey
$cfromString :: String -> SigningKey PaymentKey
IsString) via UsingRawBytesHex (SigningKey PaymentKey)
deriving newtype (Typeable (SigningKey PaymentKey)
Typeable (SigningKey PaymentKey)
-> (SigningKey PaymentKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size)
-> ToCBOR (SigningKey PaymentKey)
SigningKey PaymentKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size
toCBOR :: SigningKey PaymentKey -> Encoding
$ctoCBOR :: SigningKey PaymentKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey PaymentKey)
ToCBOR, Typeable (SigningKey PaymentKey)
Decoder s (SigningKey PaymentKey)
Typeable (SigningKey PaymentKey)
-> (forall s. Decoder s (SigningKey PaymentKey))
-> (Proxy (SigningKey PaymentKey) -> Text)
-> FromCBOR (SigningKey PaymentKey)
Proxy (SigningKey PaymentKey) -> Text
forall s. Decoder s (SigningKey PaymentKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey PaymentKey) -> Text
$clabel :: Proxy (SigningKey PaymentKey) -> Text
fromCBOR :: Decoder s (SigningKey PaymentKey)
$cfromCBOR :: forall s. Decoder s (SigningKey PaymentKey)
$cp1FromCBOR :: Typeable (SigningKey PaymentKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey PaymentKey)
HasTypeProxy (SigningKey PaymentKey)
-> (SigningKey PaymentKey -> ByteString)
-> (AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey))
-> SerialiseAsCBOR (SigningKey PaymentKey)
AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey)
SigningKey PaymentKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey)
$cdeserialiseFromCBOR :: AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey)
serialiseToCBOR :: SigningKey PaymentKey -> ByteString
$cserialiseToCBOR :: SigningKey PaymentKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey PaymentKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType PaymentKey -> Crypto.Seed -> SigningKey PaymentKey
deterministicSigningKey :: AsType PaymentKey -> Seed -> SigningKey PaymentKey
deterministicSigningKey AsType PaymentKey
AsPaymentKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
PaymentSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType PaymentKey -> Word
deterministicSigningKeySeedSize :: AsType PaymentKey -> Word
deterministicSigningKeySeedSize AsType PaymentKey
AsPaymentKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey
getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey
getVerificationKey (PaymentSigningKey sk) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey
verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey
verificationKeyHash (PaymentVerificationKey vkey) =
KeyHash 'Payment StandardCrypto -> Hash PaymentKey
PaymentKeyHash (VKey 'Payment StandardCrypto -> KeyHash 'Payment StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Payment StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey PaymentKey) where
serialiseToRawBytes :: VerificationKey PaymentKey -> ByteString
serialiseToRawBytes (PaymentVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey PaymentKey)
-> ByteString -> Maybe (VerificationKey PaymentKey)
deserialiseFromRawBytes (AsVerificationKey AsPaymentKey) ByteString
bs =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (VKey 'Payment StandardCrypto -> VerificationKey PaymentKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey PaymentKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey PaymentKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey PaymentKey) where
serialiseToRawBytes :: SigningKey PaymentKey -> ByteString
serialiseToRawBytes (PaymentSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey PaymentKey)
-> ByteString -> Maybe (SigningKey PaymentKey)
deserialiseFromRawBytes (AsSigningKey AsPaymentKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey PaymentKey
PaymentSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey PaymentKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey PaymentKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
instance SerialiseAsBech32 (VerificationKey PaymentKey) where
bech32PrefixFor :: VerificationKey PaymentKey -> Text
bech32PrefixFor VerificationKey PaymentKey
_ = Text
"addr_vk"
bech32PrefixesPermitted :: AsType (VerificationKey PaymentKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey PaymentKey)
_ = [Text
"addr_vk"]
instance SerialiseAsBech32 (SigningKey PaymentKey) where
bech32PrefixFor :: SigningKey PaymentKey -> Text
bech32PrefixFor SigningKey PaymentKey
_ = Text
"addr_sk"
bech32PrefixesPermitted :: AsType (SigningKey PaymentKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey PaymentKey)
_ = [Text
"addr_sk"]
newtype instance Hash PaymentKey =
PaymentKeyHash (Sophie.KeyHash Sophie.Payment StandardCrypto)
deriving stock (Hash PaymentKey -> Hash PaymentKey -> Bool
(Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> Eq (Hash PaymentKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c/= :: Hash PaymentKey -> Hash PaymentKey -> Bool
== :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c== :: Hash PaymentKey -> Hash PaymentKey -> Bool
Eq, Eq (Hash PaymentKey)
Eq (Hash PaymentKey)
-> (Hash PaymentKey -> Hash PaymentKey -> Ordering)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey)
-> (Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey)
-> Ord (Hash PaymentKey)
Hash PaymentKey -> Hash PaymentKey -> Bool
Hash PaymentKey -> Hash PaymentKey -> Ordering
Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
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
min :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
$cmin :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
max :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
$cmax :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
>= :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c>= :: Hash PaymentKey -> Hash PaymentKey -> Bool
> :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c> :: Hash PaymentKey -> Hash PaymentKey -> Bool
<= :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c<= :: Hash PaymentKey -> Hash PaymentKey -> Bool
< :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c< :: Hash PaymentKey -> Hash PaymentKey -> Bool
compare :: Hash PaymentKey -> Hash PaymentKey -> Ordering
$ccompare :: Hash PaymentKey -> Hash PaymentKey -> Ordering
$cp1Ord :: Eq (Hash PaymentKey)
Ord)
deriving (Int -> Hash PaymentKey -> ShowS
[Hash PaymentKey] -> ShowS
Hash PaymentKey -> String
(Int -> Hash PaymentKey -> ShowS)
-> (Hash PaymentKey -> String)
-> ([Hash PaymentKey] -> ShowS)
-> Show (Hash PaymentKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash PaymentKey] -> ShowS
$cshowList :: [Hash PaymentKey] -> ShowS
show :: Hash PaymentKey -> String
$cshow :: Hash PaymentKey -> String
showsPrec :: Int -> Hash PaymentKey -> ShowS
$cshowsPrec :: Int -> Hash PaymentKey -> ShowS
Show, String -> Hash PaymentKey
(String -> Hash PaymentKey) -> IsString (Hash PaymentKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash PaymentKey
$cfromString :: String -> Hash PaymentKey
IsString) via UsingRawBytesHex (Hash PaymentKey)
deriving (Typeable (Hash PaymentKey)
Typeable (Hash PaymentKey)
-> (Hash PaymentKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size)
-> ToCBOR (Hash PaymentKey)
Hash PaymentKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size
toCBOR :: Hash PaymentKey -> Encoding
$ctoCBOR :: Hash PaymentKey -> Encoding
$cp1ToCBOR :: Typeable (Hash PaymentKey)
ToCBOR, Typeable (Hash PaymentKey)
Decoder s (Hash PaymentKey)
Typeable (Hash PaymentKey)
-> (forall s. Decoder s (Hash PaymentKey))
-> (Proxy (Hash PaymentKey) -> Text)
-> FromCBOR (Hash PaymentKey)
Proxy (Hash PaymentKey) -> Text
forall s. Decoder s (Hash PaymentKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash PaymentKey) -> Text
$clabel :: Proxy (Hash PaymentKey) -> Text
fromCBOR :: Decoder s (Hash PaymentKey)
$cfromCBOR :: forall s. Decoder s (Hash PaymentKey)
$cp1FromCBOR :: Typeable (Hash PaymentKey)
FromCBOR) via UsingRawBytes (Hash PaymentKey)
deriving anyclass HasTypeProxy (Hash PaymentKey)
HasTypeProxy (Hash PaymentKey)
-> (Hash PaymentKey -> ByteString)
-> (AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey))
-> SerialiseAsCBOR (Hash PaymentKey)
AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey)
Hash PaymentKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey)
$cdeserialiseFromCBOR :: AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey)
serialiseToCBOR :: Hash PaymentKey -> ByteString
$cserialiseToCBOR :: Hash PaymentKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash PaymentKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash PaymentKey) where
serialiseToRawBytes :: Hash PaymentKey -> ByteString
serialiseToRawBytes (PaymentKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash PaymentKey) -> ByteString -> Maybe (Hash PaymentKey)
deserialiseFromRawBytes (AsHash AsPaymentKey) ByteString
bs =
KeyHash 'Payment StandardCrypto -> Hash PaymentKey
PaymentKeyHash (KeyHash 'Payment StandardCrypto -> Hash PaymentKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> Hash PaymentKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash PaymentKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey PaymentKey) where
textEnvelopeType :: AsType (VerificationKey PaymentKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey PaymentKey)
_ = TextEnvelopeType
"PaymentVerificationKeySophie_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey PaymentKey) where
textEnvelopeType :: AsType (SigningKey PaymentKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey PaymentKey)
_ = TextEnvelopeType
"PaymentSigningKeySophie_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
data PaymentExtendedKey
instance HasTypeProxy PaymentExtendedKey where
data AsType PaymentExtendedKey = AsPaymentExtendedKey
proxyToAsType :: Proxy PaymentExtendedKey -> AsType PaymentExtendedKey
proxyToAsType Proxy PaymentExtendedKey
_ = AsType PaymentExtendedKey
AsPaymentExtendedKey
instance Key PaymentExtendedKey where
newtype VerificationKey PaymentExtendedKey =
PaymentExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
(VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool)
-> (VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool)
-> Eq (VerificationKey PaymentExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
$c/= :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
== :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
$c== :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey PaymentExtendedKey)
HasTypeProxy (VerificationKey PaymentExtendedKey)
-> (VerificationKey PaymentExtendedKey -> ByteString)
-> (AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey))
-> SerialiseAsCBOR (VerificationKey PaymentExtendedKey)
AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey)
VerificationKey PaymentExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey)
serialiseToCBOR :: VerificationKey PaymentExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey PaymentExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey PaymentExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey PaymentExtendedKey -> ShowS
[VerificationKey PaymentExtendedKey] -> ShowS
VerificationKey PaymentExtendedKey -> String
(Int -> VerificationKey PaymentExtendedKey -> ShowS)
-> (VerificationKey PaymentExtendedKey -> String)
-> ([VerificationKey PaymentExtendedKey] -> ShowS)
-> Show (VerificationKey PaymentExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey PaymentExtendedKey] -> ShowS
$cshowList :: [VerificationKey PaymentExtendedKey] -> ShowS
show :: VerificationKey PaymentExtendedKey -> String
$cshow :: VerificationKey PaymentExtendedKey -> String
showsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS
Show, String -> VerificationKey PaymentExtendedKey
(String -> VerificationKey PaymentExtendedKey)
-> IsString (VerificationKey PaymentExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey PaymentExtendedKey
$cfromString :: String -> VerificationKey PaymentExtendedKey
IsString) via UsingRawBytesHex (VerificationKey PaymentExtendedKey)
newtype SigningKey PaymentExtendedKey =
PaymentExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey PaymentExtendedKey)
HasTypeProxy (SigningKey PaymentExtendedKey)
-> (SigningKey PaymentExtendedKey -> ByteString)
-> (AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey))
-> SerialiseAsCBOR (SigningKey PaymentExtendedKey)
AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey)
SigningKey PaymentExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey)
serialiseToCBOR :: SigningKey PaymentExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey PaymentExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey PaymentExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey PaymentExtendedKey -> ShowS
[SigningKey PaymentExtendedKey] -> ShowS
SigningKey PaymentExtendedKey -> String
(Int -> SigningKey PaymentExtendedKey -> ShowS)
-> (SigningKey PaymentExtendedKey -> String)
-> ([SigningKey PaymentExtendedKey] -> ShowS)
-> Show (SigningKey PaymentExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey PaymentExtendedKey] -> ShowS
$cshowList :: [SigningKey PaymentExtendedKey] -> ShowS
show :: SigningKey PaymentExtendedKey -> String
$cshow :: SigningKey PaymentExtendedKey -> String
showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS
Show, String -> SigningKey PaymentExtendedKey
(String -> SigningKey PaymentExtendedKey)
-> IsString (SigningKey PaymentExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey PaymentExtendedKey
$cfromString :: String -> SigningKey PaymentExtendedKey
IsString) via UsingRawBytesHex (SigningKey PaymentExtendedKey)
deterministicSigningKey :: AsType PaymentExtendedKey
-> Crypto.Seed
-> SigningKey PaymentExtendedKey
deterministicSigningKey :: AsType PaymentExtendedKey -> Seed -> SigningKey PaymentExtendedKey
deterministicSigningKey AsType PaymentExtendedKey
AsPaymentExtendedKey Seed
seed =
XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word
deterministicSigningKeySeedSize AsType PaymentExtendedKey
AsPaymentExtendedKey = Word
32
getVerificationKey :: SigningKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey
getVerificationKey :: SigningKey PaymentExtendedKey -> VerificationKey PaymentExtendedKey
getVerificationKey (PaymentExtendedSigningKey sk) =
XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey PaymentExtendedKey
-> Hash PaymentExtendedKey
verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey
verificationKeyHash (PaymentExtendedVerificationKey vk) =
KeyHash 'Payment StandardCrypto -> Hash PaymentExtendedKey
PaymentExtendedKeyHash
(KeyHash 'Payment StandardCrypto -> Hash PaymentExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Payment StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash PaymentExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Payment StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash PaymentExtendedKey)
-> Hash Blake2b_224 XPub -> Hash PaymentExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey PaymentExtendedKey) where
toCBOR :: VerificationKey PaymentExtendedKey -> Encoding
toCBOR (PaymentExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey PaymentExtendedKey) where
fromCBOR :: Decoder s (VerificationKey PaymentExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey PaymentExtendedKey))
-> (XPub -> Decoder s (VerificationKey PaymentExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey PaymentExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey PaymentExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey PaymentExtendedKey
-> Decoder s (VerificationKey PaymentExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey PaymentExtendedKey
-> Decoder s (VerificationKey PaymentExtendedKey))
-> (XPub -> VerificationKey PaymentExtendedKey)
-> XPub
-> Decoder s (VerificationKey PaymentExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey PaymentExtendedKey) where
toCBOR :: SigningKey PaymentExtendedKey -> Encoding
toCBOR (PaymentExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey PaymentExtendedKey) where
fromCBOR :: Decoder s (SigningKey PaymentExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey PaymentExtendedKey))
-> (XPrv -> Decoder s (SigningKey PaymentExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey PaymentExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey PaymentExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey PaymentExtendedKey
-> Decoder s (SigningKey PaymentExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey PaymentExtendedKey
-> Decoder s (SigningKey PaymentExtendedKey))
-> (XPrv -> SigningKey PaymentExtendedKey)
-> XPrv
-> Decoder s (SigningKey PaymentExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) where
serialiseToRawBytes :: VerificationKey PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey PaymentExtendedKey)
-> ByteString -> Maybe (VerificationKey PaymentExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsPaymentExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey PaymentExtendedKey))
-> (XPub -> Maybe (VerificationKey PaymentExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey PaymentExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey PaymentExtendedKey)
-> String -> Maybe (VerificationKey PaymentExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey PaymentExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey PaymentExtendedKey
-> Maybe (VerificationKey PaymentExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey PaymentExtendedKey
-> Maybe (VerificationKey PaymentExtendedKey))
-> (XPub -> VerificationKey PaymentExtendedKey)
-> XPub
-> Maybe (VerificationKey PaymentExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey PaymentExtendedKey) where
serialiseToRawBytes :: SigningKey PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey PaymentExtendedKey)
-> ByteString -> Maybe (SigningKey PaymentExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsPaymentExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey PaymentExtendedKey))
-> (XPrv -> Maybe (SigningKey PaymentExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey PaymentExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey PaymentExtendedKey)
-> String -> Maybe (SigningKey PaymentExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey PaymentExtendedKey)
forall a. Maybe a
Nothing) (SigningKey PaymentExtendedKey
-> Maybe (SigningKey PaymentExtendedKey)
forall a. a -> Maybe a
Just (SigningKey PaymentExtendedKey
-> Maybe (SigningKey PaymentExtendedKey))
-> (XPrv -> SigningKey PaymentExtendedKey)
-> XPrv
-> Maybe (SigningKey PaymentExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
instance SerialiseAsBech32 (VerificationKey PaymentExtendedKey) where
bech32PrefixFor :: VerificationKey PaymentExtendedKey -> Text
bech32PrefixFor VerificationKey PaymentExtendedKey
_ = Text
"addr_xvk"
bech32PrefixesPermitted :: AsType (VerificationKey PaymentExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey PaymentExtendedKey)
_ = [Text
"addr_xvk"]
instance SerialiseAsBech32 (SigningKey PaymentExtendedKey) where
bech32PrefixFor :: SigningKey PaymentExtendedKey -> Text
bech32PrefixFor SigningKey PaymentExtendedKey
_ = Text
"addr_xsk"
bech32PrefixesPermitted :: AsType (SigningKey PaymentExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey PaymentExtendedKey)
_ = [Text
"addr_xsk"]
newtype instance Hash PaymentExtendedKey =
PaymentExtendedKeyHash (Sophie.KeyHash Sophie.Payment StandardCrypto)
deriving stock (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
(Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> Eq (Hash PaymentExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c/= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
== :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c== :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
Eq, Eq (Hash PaymentExtendedKey)
Eq (Hash PaymentExtendedKey)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey)
-> (Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey)
-> Ord (Hash PaymentExtendedKey)
Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering
Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
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
min :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
$cmin :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
max :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
$cmax :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
>= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c>= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
> :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c> :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
<= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c<= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
< :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c< :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
compare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering
$ccompare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering
$cp1Ord :: Eq (Hash PaymentExtendedKey)
Ord)
deriving (Int -> Hash PaymentExtendedKey -> ShowS
[Hash PaymentExtendedKey] -> ShowS
Hash PaymentExtendedKey -> String
(Int -> Hash PaymentExtendedKey -> ShowS)
-> (Hash PaymentExtendedKey -> String)
-> ([Hash PaymentExtendedKey] -> ShowS)
-> Show (Hash PaymentExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash PaymentExtendedKey] -> ShowS
$cshowList :: [Hash PaymentExtendedKey] -> ShowS
show :: Hash PaymentExtendedKey -> String
$cshow :: Hash PaymentExtendedKey -> String
showsPrec :: Int -> Hash PaymentExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash PaymentExtendedKey -> ShowS
Show, String -> Hash PaymentExtendedKey
(String -> Hash PaymentExtendedKey)
-> IsString (Hash PaymentExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash PaymentExtendedKey
$cfromString :: String -> Hash PaymentExtendedKey
IsString) via UsingRawBytesHex (Hash PaymentExtendedKey)
deriving (Typeable (Hash PaymentExtendedKey)
Typeable (Hash PaymentExtendedKey)
-> (Hash PaymentExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size)
-> ToCBOR (Hash PaymentExtendedKey)
Hash PaymentExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size
toCBOR :: Hash PaymentExtendedKey -> Encoding
$ctoCBOR :: Hash PaymentExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash PaymentExtendedKey)
ToCBOR, Typeable (Hash PaymentExtendedKey)
Decoder s (Hash PaymentExtendedKey)
Typeable (Hash PaymentExtendedKey)
-> (forall s. Decoder s (Hash PaymentExtendedKey))
-> (Proxy (Hash PaymentExtendedKey) -> Text)
-> FromCBOR (Hash PaymentExtendedKey)
Proxy (Hash PaymentExtendedKey) -> Text
forall s. Decoder s (Hash PaymentExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash PaymentExtendedKey) -> Text
$clabel :: Proxy (Hash PaymentExtendedKey) -> Text
fromCBOR :: Decoder s (Hash PaymentExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash PaymentExtendedKey)
$cp1FromCBOR :: Typeable (Hash PaymentExtendedKey)
FromCBOR) via UsingRawBytes (Hash PaymentExtendedKey)
deriving anyclass HasTypeProxy (Hash PaymentExtendedKey)
HasTypeProxy (Hash PaymentExtendedKey)
-> (Hash PaymentExtendedKey -> ByteString)
-> (AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey))
-> SerialiseAsCBOR (Hash PaymentExtendedKey)
AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey)
Hash PaymentExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey)
serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString
$cserialiseToCBOR :: Hash PaymentExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash PaymentExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash PaymentExtendedKey) where
serialiseToRawBytes :: Hash PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash PaymentExtendedKey)
-> ByteString -> Maybe (Hash PaymentExtendedKey)
deserialiseFromRawBytes (AsHash AsPaymentExtendedKey) ByteString
bs =
KeyHash 'Payment StandardCrypto -> Hash PaymentExtendedKey
PaymentExtendedKeyHash (KeyHash 'Payment StandardCrypto -> Hash PaymentExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash PaymentExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash PaymentExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash PaymentExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey PaymentExtendedKey) where
textEnvelopeType :: AsType (VerificationKey PaymentExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey PaymentExtendedKey)
_ = TextEnvelopeType
"PaymentExtendedVerificationKeySophie_ed25519_bip32"
instance HasTextEnvelope (SigningKey PaymentExtendedKey) where
textEnvelopeType :: AsType (SigningKey PaymentExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey PaymentExtendedKey)
_ = TextEnvelopeType
"PaymentExtendedSigningKeySophie_ed25519_bip32"
instance CastVerificationKeyRole PaymentExtendedKey PaymentKey where
castVerificationKey :: VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey
castVerificationKey (PaymentExtendedVerificationKey vk) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey
(VKey 'Payment StandardCrypto -> VerificationKey PaymentKey)
-> (XPub -> VKey 'Payment StandardCrypto)
-> XPub
-> VerificationKey PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'Payment StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey PaymentKey)
-> XPub -> VerificationKey PaymentKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data StakeKey
instance HasTypeProxy StakeKey where
data AsType StakeKey = AsStakeKey
proxyToAsType :: Proxy StakeKey -> AsType StakeKey
proxyToAsType Proxy StakeKey
_ = AsType StakeKey
AsStakeKey
instance Key StakeKey where
newtype VerificationKey StakeKey =
StakeVerificationKey (Sophie.VKey Sophie.Staking StandardCrypto)
deriving stock (VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
(VerificationKey StakeKey -> VerificationKey StakeKey -> Bool)
-> (VerificationKey StakeKey -> VerificationKey StakeKey -> Bool)
-> Eq (VerificationKey StakeKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
$c/= :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
== :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
$c== :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
Eq)
deriving newtype (Typeable (VerificationKey StakeKey)
Typeable (VerificationKey StakeKey)
-> (VerificationKey StakeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size)
-> ToCBOR (VerificationKey StakeKey)
VerificationKey StakeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size
toCBOR :: VerificationKey StakeKey -> Encoding
$ctoCBOR :: VerificationKey StakeKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey StakeKey)
ToCBOR, Typeable (VerificationKey StakeKey)
Decoder s (VerificationKey StakeKey)
Typeable (VerificationKey StakeKey)
-> (forall s. Decoder s (VerificationKey StakeKey))
-> (Proxy (VerificationKey StakeKey) -> Text)
-> FromCBOR (VerificationKey StakeKey)
Proxy (VerificationKey StakeKey) -> Text
forall s. Decoder s (VerificationKey StakeKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey StakeKey) -> Text
$clabel :: Proxy (VerificationKey StakeKey) -> Text
fromCBOR :: Decoder s (VerificationKey StakeKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey StakeKey)
$cp1FromCBOR :: Typeable (VerificationKey StakeKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey StakeKey)
HasTypeProxy (VerificationKey StakeKey)
-> (VerificationKey StakeKey -> ByteString)
-> (AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey))
-> SerialiseAsCBOR (VerificationKey StakeKey)
AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey)
VerificationKey StakeKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey)
serialiseToCBOR :: VerificationKey StakeKey -> ByteString
$cserialiseToCBOR :: VerificationKey StakeKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey StakeKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey StakeKey -> ShowS
[VerificationKey StakeKey] -> ShowS
VerificationKey StakeKey -> String
(Int -> VerificationKey StakeKey -> ShowS)
-> (VerificationKey StakeKey -> String)
-> ([VerificationKey StakeKey] -> ShowS)
-> Show (VerificationKey StakeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey StakeKey] -> ShowS
$cshowList :: [VerificationKey StakeKey] -> ShowS
show :: VerificationKey StakeKey -> String
$cshow :: VerificationKey StakeKey -> String
showsPrec :: Int -> VerificationKey StakeKey -> ShowS
$cshowsPrec :: Int -> VerificationKey StakeKey -> ShowS
Show, String -> VerificationKey StakeKey
(String -> VerificationKey StakeKey)
-> IsString (VerificationKey StakeKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey StakeKey
$cfromString :: String -> VerificationKey StakeKey
IsString) via UsingRawBytesHex (VerificationKey StakeKey)
newtype SigningKey StakeKey =
StakeSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving newtype (Typeable (SigningKey StakeKey)
Typeable (SigningKey StakeKey)
-> (SigningKey StakeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size)
-> ToCBOR (SigningKey StakeKey)
SigningKey StakeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size
toCBOR :: SigningKey StakeKey -> Encoding
$ctoCBOR :: SigningKey StakeKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey StakeKey)
ToCBOR, Typeable (SigningKey StakeKey)
Decoder s (SigningKey StakeKey)
Typeable (SigningKey StakeKey)
-> (forall s. Decoder s (SigningKey StakeKey))
-> (Proxy (SigningKey StakeKey) -> Text)
-> FromCBOR (SigningKey StakeKey)
Proxy (SigningKey StakeKey) -> Text
forall s. Decoder s (SigningKey StakeKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey StakeKey) -> Text
$clabel :: Proxy (SigningKey StakeKey) -> Text
fromCBOR :: Decoder s (SigningKey StakeKey)
$cfromCBOR :: forall s. Decoder s (SigningKey StakeKey)
$cp1FromCBOR :: Typeable (SigningKey StakeKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey StakeKey)
HasTypeProxy (SigningKey StakeKey)
-> (SigningKey StakeKey -> ByteString)
-> (AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey))
-> SerialiseAsCBOR (SigningKey StakeKey)
AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey)
SigningKey StakeKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey)
$cdeserialiseFromCBOR :: AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey)
serialiseToCBOR :: SigningKey StakeKey -> ByteString
$cserialiseToCBOR :: SigningKey StakeKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey StakeKey)
SerialiseAsCBOR
deriving (Int -> SigningKey StakeKey -> ShowS
[SigningKey StakeKey] -> ShowS
SigningKey StakeKey -> String
(Int -> SigningKey StakeKey -> ShowS)
-> (SigningKey StakeKey -> String)
-> ([SigningKey StakeKey] -> ShowS)
-> Show (SigningKey StakeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey StakeKey] -> ShowS
$cshowList :: [SigningKey StakeKey] -> ShowS
show :: SigningKey StakeKey -> String
$cshow :: SigningKey StakeKey -> String
showsPrec :: Int -> SigningKey StakeKey -> ShowS
$cshowsPrec :: Int -> SigningKey StakeKey -> ShowS
Show, String -> SigningKey StakeKey
(String -> SigningKey StakeKey) -> IsString (SigningKey StakeKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey StakeKey
$cfromString :: String -> SigningKey StakeKey
IsString) via UsingRawBytesHex (SigningKey StakeKey)
deterministicSigningKey :: AsType StakeKey -> Crypto.Seed -> SigningKey StakeKey
deterministicSigningKey :: AsType StakeKey -> Seed -> SigningKey StakeKey
deterministicSigningKey AsType StakeKey
AsStakeKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey StakeKey
StakeSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType StakeKey -> Word
deterministicSigningKeySeedSize :: AsType StakeKey -> Word
deterministicSigningKeySeedSize AsType StakeKey
AsStakeKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey
getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey
getVerificationKey (StakeSigningKey sk) =
VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Staking StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey
verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey
verificationKeyHash (StakeVerificationKey vkey) =
KeyHash 'Staking StandardCrypto -> Hash StakeKey
StakeKeyHash (VKey 'Staking StandardCrypto -> KeyHash 'Staking StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Staking StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey StakeKey) where
serialiseToRawBytes :: VerificationKey StakeKey -> ByteString
serialiseToRawBytes (StakeVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey StakeKey)
-> ByteString -> Maybe (VerificationKey StakeKey)
deserialiseFromRawBytes (AsVerificationKey AsStakeKey) ByteString
bs =
VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey (VKey 'Staking StandardCrypto -> VerificationKey StakeKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Staking StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey StakeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Staking StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey StakeKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey StakeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey StakeKey) where
serialiseToRawBytes :: SigningKey StakeKey -> ByteString
serialiseToRawBytes (StakeSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey StakeKey)
-> ByteString -> Maybe (SigningKey StakeKey)
deserialiseFromRawBytes (AsSigningKey AsStakeKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey StakeKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey StakeKey
StakeSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey StakeKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN) -> Maybe (SigningKey StakeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
instance SerialiseAsBech32 (VerificationKey StakeKey) where
bech32PrefixFor :: VerificationKey StakeKey -> Text
bech32PrefixFor VerificationKey StakeKey
_ = Text
"stake_vk"
bech32PrefixesPermitted :: AsType (VerificationKey StakeKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey StakeKey)
_ = [Text
"stake_vk"]
instance SerialiseAsBech32 (SigningKey StakeKey) where
bech32PrefixFor :: SigningKey StakeKey -> Text
bech32PrefixFor SigningKey StakeKey
_ = Text
"stake_sk"
bech32PrefixesPermitted :: AsType (SigningKey StakeKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey StakeKey)
_ = [Text
"stake_sk"]
newtype instance Hash StakeKey =
StakeKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash StakeKey -> Hash StakeKey -> Bool
(Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool) -> Eq (Hash StakeKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash StakeKey -> Hash StakeKey -> Bool
$c/= :: Hash StakeKey -> Hash StakeKey -> Bool
== :: Hash StakeKey -> Hash StakeKey -> Bool
$c== :: Hash StakeKey -> Hash StakeKey -> Bool
Eq, Eq (Hash StakeKey)
Eq (Hash StakeKey)
-> (Hash StakeKey -> Hash StakeKey -> Ordering)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Hash StakeKey)
-> (Hash StakeKey -> Hash StakeKey -> Hash StakeKey)
-> Ord (Hash StakeKey)
Hash StakeKey -> Hash StakeKey -> Bool
Hash StakeKey -> Hash StakeKey -> Ordering
Hash StakeKey -> Hash StakeKey -> Hash StakeKey
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
min :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
$cmin :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
max :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
$cmax :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
>= :: Hash StakeKey -> Hash StakeKey -> Bool
$c>= :: Hash StakeKey -> Hash StakeKey -> Bool
> :: Hash StakeKey -> Hash StakeKey -> Bool
$c> :: Hash StakeKey -> Hash StakeKey -> Bool
<= :: Hash StakeKey -> Hash StakeKey -> Bool
$c<= :: Hash StakeKey -> Hash StakeKey -> Bool
< :: Hash StakeKey -> Hash StakeKey -> Bool
$c< :: Hash StakeKey -> Hash StakeKey -> Bool
compare :: Hash StakeKey -> Hash StakeKey -> Ordering
$ccompare :: Hash StakeKey -> Hash StakeKey -> Ordering
$cp1Ord :: Eq (Hash StakeKey)
Ord)
deriving (Int -> Hash StakeKey -> ShowS
[Hash StakeKey] -> ShowS
Hash StakeKey -> String
(Int -> Hash StakeKey -> ShowS)
-> (Hash StakeKey -> String)
-> ([Hash StakeKey] -> ShowS)
-> Show (Hash StakeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash StakeKey] -> ShowS
$cshowList :: [Hash StakeKey] -> ShowS
show :: Hash StakeKey -> String
$cshow :: Hash StakeKey -> String
showsPrec :: Int -> Hash StakeKey -> ShowS
$cshowsPrec :: Int -> Hash StakeKey -> ShowS
Show, String -> Hash StakeKey
(String -> Hash StakeKey) -> IsString (Hash StakeKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash StakeKey
$cfromString :: String -> Hash StakeKey
IsString) via UsingRawBytesHex (Hash StakeKey)
deriving (Typeable (Hash StakeKey)
Typeable (Hash StakeKey)
-> (Hash StakeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size)
-> ToCBOR (Hash StakeKey)
Hash StakeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size
toCBOR :: Hash StakeKey -> Encoding
$ctoCBOR :: Hash StakeKey -> Encoding
$cp1ToCBOR :: Typeable (Hash StakeKey)
ToCBOR, Typeable (Hash StakeKey)
Decoder s (Hash StakeKey)
Typeable (Hash StakeKey)
-> (forall s. Decoder s (Hash StakeKey))
-> (Proxy (Hash StakeKey) -> Text)
-> FromCBOR (Hash StakeKey)
Proxy (Hash StakeKey) -> Text
forall s. Decoder s (Hash StakeKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash StakeKey) -> Text
$clabel :: Proxy (Hash StakeKey) -> Text
fromCBOR :: Decoder s (Hash StakeKey)
$cfromCBOR :: forall s. Decoder s (Hash StakeKey)
$cp1FromCBOR :: Typeable (Hash StakeKey)
FromCBOR) via UsingRawBytes (Hash StakeKey)
deriving anyclass HasTypeProxy (Hash StakeKey)
HasTypeProxy (Hash StakeKey)
-> (Hash StakeKey -> ByteString)
-> (AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey))
-> SerialiseAsCBOR (Hash StakeKey)
AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey)
Hash StakeKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey)
$cdeserialiseFromCBOR :: AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey)
serialiseToCBOR :: Hash StakeKey -> ByteString
$cserialiseToCBOR :: Hash StakeKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash StakeKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash StakeKey) where
serialiseToRawBytes :: Hash StakeKey -> ByteString
serialiseToRawBytes (StakeKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash StakeKey) -> ByteString -> Maybe (Hash StakeKey)
deserialiseFromRawBytes (AsHash AsStakeKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash StakeKey
StakeKeyHash (KeyHash 'Staking StandardCrypto -> Hash StakeKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash StakeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> Hash StakeKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash StakeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey StakeKey) where
textEnvelopeType :: AsType (VerificationKey StakeKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey StakeKey)
_ = TextEnvelopeType
"StakeVerificationKeySophie_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey StakeKey) where
textEnvelopeType :: AsType (SigningKey StakeKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakeKey)
_ = TextEnvelopeType
"StakeSigningKeySophie_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
data StakeExtendedKey
instance HasTypeProxy StakeExtendedKey where
data AsType StakeExtendedKey = AsStakeExtendedKey
proxyToAsType :: Proxy StakeExtendedKey -> AsType StakeExtendedKey
proxyToAsType Proxy StakeExtendedKey
_ = AsType StakeExtendedKey
AsStakeExtendedKey
instance Key StakeExtendedKey where
newtype VerificationKey StakeExtendedKey =
StakeExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
(VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool)
-> (VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool)
-> Eq (VerificationKey StakeExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
$c/= :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
== :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
$c== :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey StakeExtendedKey)
HasTypeProxy (VerificationKey StakeExtendedKey)
-> (VerificationKey StakeExtendedKey -> ByteString)
-> (AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey))
-> SerialiseAsCBOR (VerificationKey StakeExtendedKey)
AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey)
VerificationKey StakeExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey)
serialiseToCBOR :: VerificationKey StakeExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey StakeExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey StakeExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey StakeExtendedKey -> ShowS
[VerificationKey StakeExtendedKey] -> ShowS
VerificationKey StakeExtendedKey -> String
(Int -> VerificationKey StakeExtendedKey -> ShowS)
-> (VerificationKey StakeExtendedKey -> String)
-> ([VerificationKey StakeExtendedKey] -> ShowS)
-> Show (VerificationKey StakeExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey StakeExtendedKey] -> ShowS
$cshowList :: [VerificationKey StakeExtendedKey] -> ShowS
show :: VerificationKey StakeExtendedKey -> String
$cshow :: VerificationKey StakeExtendedKey -> String
showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS
Show, String -> VerificationKey StakeExtendedKey
(String -> VerificationKey StakeExtendedKey)
-> IsString (VerificationKey StakeExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey StakeExtendedKey
$cfromString :: String -> VerificationKey StakeExtendedKey
IsString) via UsingRawBytesHex (VerificationKey StakeExtendedKey)
newtype SigningKey StakeExtendedKey =
StakeExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey StakeExtendedKey)
HasTypeProxy (SigningKey StakeExtendedKey)
-> (SigningKey StakeExtendedKey -> ByteString)
-> (AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey))
-> SerialiseAsCBOR (SigningKey StakeExtendedKey)
AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey)
SigningKey StakeExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey)
serialiseToCBOR :: SigningKey StakeExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey StakeExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey StakeExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey StakeExtendedKey -> ShowS
[SigningKey StakeExtendedKey] -> ShowS
SigningKey StakeExtendedKey -> String
(Int -> SigningKey StakeExtendedKey -> ShowS)
-> (SigningKey StakeExtendedKey -> String)
-> ([SigningKey StakeExtendedKey] -> ShowS)
-> Show (SigningKey StakeExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey StakeExtendedKey] -> ShowS
$cshowList :: [SigningKey StakeExtendedKey] -> ShowS
show :: SigningKey StakeExtendedKey -> String
$cshow :: SigningKey StakeExtendedKey -> String
showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS
Show, String -> SigningKey StakeExtendedKey
(String -> SigningKey StakeExtendedKey)
-> IsString (SigningKey StakeExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey StakeExtendedKey
$cfromString :: String -> SigningKey StakeExtendedKey
IsString) via UsingRawBytesHex (SigningKey StakeExtendedKey)
deterministicSigningKey :: AsType StakeExtendedKey
-> Crypto.Seed
-> SigningKey StakeExtendedKey
deterministicSigningKey :: AsType StakeExtendedKey -> Seed -> SigningKey StakeExtendedKey
deterministicSigningKey AsType StakeExtendedKey
AsStakeExtendedKey Seed
seed =
XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word
deterministicSigningKeySeedSize AsType StakeExtendedKey
AsStakeExtendedKey = Word
32
getVerificationKey :: SigningKey StakeExtendedKey
-> VerificationKey StakeExtendedKey
getVerificationKey :: SigningKey StakeExtendedKey -> VerificationKey StakeExtendedKey
getVerificationKey (StakeExtendedSigningKey sk) =
XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey StakeExtendedKey
-> Hash StakeExtendedKey
verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey
verificationKeyHash (StakeExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto -> Hash StakeExtendedKey
StakeExtendedKeyHash
(KeyHash 'Staking StandardCrypto -> Hash StakeExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash StakeExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash StakeExtendedKey)
-> Hash Blake2b_224 XPub -> Hash StakeExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey StakeExtendedKey) where
toCBOR :: VerificationKey StakeExtendedKey -> Encoding
toCBOR (StakeExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey StakeExtendedKey) where
fromCBOR :: Decoder s (VerificationKey StakeExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey StakeExtendedKey))
-> (XPub -> Decoder s (VerificationKey StakeExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey StakeExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey StakeExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey StakeExtendedKey
-> Decoder s (VerificationKey StakeExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey StakeExtendedKey
-> Decoder s (VerificationKey StakeExtendedKey))
-> (XPub -> VerificationKey StakeExtendedKey)
-> XPub
-> Decoder s (VerificationKey StakeExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey StakeExtendedKey) where
toCBOR :: SigningKey StakeExtendedKey -> Encoding
toCBOR (StakeExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey StakeExtendedKey) where
fromCBOR :: Decoder s (SigningKey StakeExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey StakeExtendedKey))
-> (XPrv -> Decoder s (SigningKey StakeExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey StakeExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey StakeExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey StakeExtendedKey
-> Decoder s (SigningKey StakeExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey StakeExtendedKey
-> Decoder s (SigningKey StakeExtendedKey))
-> (XPrv -> SigningKey StakeExtendedKey)
-> XPrv
-> Decoder s (SigningKey StakeExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey StakeExtendedKey) where
serialiseToRawBytes :: VerificationKey StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey StakeExtendedKey)
-> ByteString -> Maybe (VerificationKey StakeExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsStakeExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey StakeExtendedKey))
-> (XPub -> Maybe (VerificationKey StakeExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey StakeExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey StakeExtendedKey)
-> String -> Maybe (VerificationKey StakeExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey StakeExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey StakeExtendedKey
-> Maybe (VerificationKey StakeExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey StakeExtendedKey
-> Maybe (VerificationKey StakeExtendedKey))
-> (XPub -> VerificationKey StakeExtendedKey)
-> XPub
-> Maybe (VerificationKey StakeExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey StakeExtendedKey) where
serialiseToRawBytes :: SigningKey StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey StakeExtendedKey)
-> ByteString -> Maybe (SigningKey StakeExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsStakeExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey StakeExtendedKey))
-> (XPrv -> Maybe (SigningKey StakeExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey StakeExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey StakeExtendedKey)
-> String -> Maybe (SigningKey StakeExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey StakeExtendedKey)
forall a. Maybe a
Nothing) (SigningKey StakeExtendedKey -> Maybe (SigningKey StakeExtendedKey)
forall a. a -> Maybe a
Just (SigningKey StakeExtendedKey
-> Maybe (SigningKey StakeExtendedKey))
-> (XPrv -> SigningKey StakeExtendedKey)
-> XPrv
-> Maybe (SigningKey StakeExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
instance SerialiseAsBech32 (VerificationKey StakeExtendedKey) where
bech32PrefixFor :: VerificationKey StakeExtendedKey -> Text
bech32PrefixFor VerificationKey StakeExtendedKey
_ = Text
"stake_xvk"
bech32PrefixesPermitted :: AsType (VerificationKey StakeExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey StakeExtendedKey)
_ = [Text
"stake_xvk"]
instance SerialiseAsBech32 (SigningKey StakeExtendedKey) where
bech32PrefixFor :: SigningKey StakeExtendedKey -> Text
bech32PrefixFor SigningKey StakeExtendedKey
_ = Text
"stake_xsk"
bech32PrefixesPermitted :: AsType (SigningKey StakeExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey StakeExtendedKey)
_ = [Text
"stake_xsk"]
newtype instance Hash StakeExtendedKey =
StakeExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
(Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> Eq (Hash StakeExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c/= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
== :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c== :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
Eq, Eq (Hash StakeExtendedKey)
Eq (Hash StakeExtendedKey)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey)
-> (Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey)
-> Ord (Hash StakeExtendedKey)
Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering
Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
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
min :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
$cmin :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
max :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
$cmax :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
>= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c>= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
> :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c> :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
<= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c<= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
< :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c< :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
compare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering
$ccompare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering
$cp1Ord :: Eq (Hash StakeExtendedKey)
Ord)
deriving (Int -> Hash StakeExtendedKey -> ShowS
[Hash StakeExtendedKey] -> ShowS
Hash StakeExtendedKey -> String
(Int -> Hash StakeExtendedKey -> ShowS)
-> (Hash StakeExtendedKey -> String)
-> ([Hash StakeExtendedKey] -> ShowS)
-> Show (Hash StakeExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash StakeExtendedKey] -> ShowS
$cshowList :: [Hash StakeExtendedKey] -> ShowS
show :: Hash StakeExtendedKey -> String
$cshow :: Hash StakeExtendedKey -> String
showsPrec :: Int -> Hash StakeExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash StakeExtendedKey -> ShowS
Show, String -> Hash StakeExtendedKey
(String -> Hash StakeExtendedKey)
-> IsString (Hash StakeExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash StakeExtendedKey
$cfromString :: String -> Hash StakeExtendedKey
IsString) via UsingRawBytesHex (Hash StakeExtendedKey)
deriving (Typeable (Hash StakeExtendedKey)
Typeable (Hash StakeExtendedKey)
-> (Hash StakeExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size)
-> ToCBOR (Hash StakeExtendedKey)
Hash StakeExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size
toCBOR :: Hash StakeExtendedKey -> Encoding
$ctoCBOR :: Hash StakeExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash StakeExtendedKey)
ToCBOR, Typeable (Hash StakeExtendedKey)
Decoder s (Hash StakeExtendedKey)
Typeable (Hash StakeExtendedKey)
-> (forall s. Decoder s (Hash StakeExtendedKey))
-> (Proxy (Hash StakeExtendedKey) -> Text)
-> FromCBOR (Hash StakeExtendedKey)
Proxy (Hash StakeExtendedKey) -> Text
forall s. Decoder s (Hash StakeExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash StakeExtendedKey) -> Text
$clabel :: Proxy (Hash StakeExtendedKey) -> Text
fromCBOR :: Decoder s (Hash StakeExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash StakeExtendedKey)
$cp1FromCBOR :: Typeable (Hash StakeExtendedKey)
FromCBOR) via UsingRawBytes (Hash StakeExtendedKey)
deriving anyclass HasTypeProxy (Hash StakeExtendedKey)
HasTypeProxy (Hash StakeExtendedKey)
-> (Hash StakeExtendedKey -> ByteString)
-> (AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey))
-> SerialiseAsCBOR (Hash StakeExtendedKey)
AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey)
Hash StakeExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey)
serialiseToCBOR :: Hash StakeExtendedKey -> ByteString
$cserialiseToCBOR :: Hash StakeExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash StakeExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash StakeExtendedKey) where
serialiseToRawBytes :: Hash StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash StakeExtendedKey)
-> ByteString -> Maybe (Hash StakeExtendedKey)
deserialiseFromRawBytes (AsHash AsStakeExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash StakeExtendedKey
StakeExtendedKeyHash (KeyHash 'Staking StandardCrypto -> Hash StakeExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash StakeExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash StakeExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash StakeExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey StakeExtendedKey) where
textEnvelopeType :: AsType (VerificationKey StakeExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey StakeExtendedKey)
_ = TextEnvelopeType
"StakeExtendedVerificationKeySophie_ed25519_bip32"
instance HasTextEnvelope (SigningKey StakeExtendedKey) where
textEnvelopeType :: AsType (SigningKey StakeExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakeExtendedKey)
_ = TextEnvelopeType
"StakeExtendedSigningKeySophie_ed25519_bip32"
instance CastVerificationKeyRole StakeExtendedKey StakeKey where
castVerificationKey :: VerificationKey StakeExtendedKey -> VerificationKey StakeKey
castVerificationKey (StakeExtendedVerificationKey vk) =
VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey
(VKey 'Staking StandardCrypto -> VerificationKey StakeKey)
-> (XPub -> VKey 'Staking StandardCrypto)
-> XPub
-> VerificationKey StakeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Staking StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'Staking StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey StakeKey)
-> XPub -> VerificationKey StakeKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data GenesisKey
instance HasTypeProxy GenesisKey where
data AsType GenesisKey = AsGenesisKey
proxyToAsType :: Proxy GenesisKey -> AsType GenesisKey
proxyToAsType Proxy GenesisKey
_ = AsType GenesisKey
AsGenesisKey
instance Key GenesisKey where
newtype VerificationKey GenesisKey =
GenesisVerificationKey (Sophie.VKey Sophie.Genesis StandardCrypto)
deriving stock (VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
(VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool)
-> (VerificationKey GenesisKey
-> VerificationKey GenesisKey -> Bool)
-> Eq (VerificationKey GenesisKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
$c/= :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
== :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
$c== :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
Eq)
deriving (Int -> VerificationKey GenesisKey -> ShowS
[VerificationKey GenesisKey] -> ShowS
VerificationKey GenesisKey -> String
(Int -> VerificationKey GenesisKey -> ShowS)
-> (VerificationKey GenesisKey -> String)
-> ([VerificationKey GenesisKey] -> ShowS)
-> Show (VerificationKey GenesisKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisKey] -> ShowS
$cshowList :: [VerificationKey GenesisKey] -> ShowS
show :: VerificationKey GenesisKey -> String
$cshow :: VerificationKey GenesisKey -> String
showsPrec :: Int -> VerificationKey GenesisKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisKey -> ShowS
Show, String -> VerificationKey GenesisKey
(String -> VerificationKey GenesisKey)
-> IsString (VerificationKey GenesisKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisKey
$cfromString :: String -> VerificationKey GenesisKey
IsString) via UsingRawBytesHex (VerificationKey GenesisKey)
deriving newtype (Typeable (VerificationKey GenesisKey)
Typeable (VerificationKey GenesisKey)
-> (VerificationKey GenesisKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size)
-> ToCBOR (VerificationKey GenesisKey)
VerificationKey GenesisKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size
toCBOR :: VerificationKey GenesisKey -> Encoding
$ctoCBOR :: VerificationKey GenesisKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey GenesisKey)
ToCBOR, Typeable (VerificationKey GenesisKey)
Decoder s (VerificationKey GenesisKey)
Typeable (VerificationKey GenesisKey)
-> (forall s. Decoder s (VerificationKey GenesisKey))
-> (Proxy (VerificationKey GenesisKey) -> Text)
-> FromCBOR (VerificationKey GenesisKey)
Proxy (VerificationKey GenesisKey) -> Text
forall s. Decoder s (VerificationKey GenesisKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey GenesisKey) -> Text
$clabel :: Proxy (VerificationKey GenesisKey) -> Text
fromCBOR :: Decoder s (VerificationKey GenesisKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisKey)
$cp1FromCBOR :: Typeable (VerificationKey GenesisKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey GenesisKey)
HasTypeProxy (VerificationKey GenesisKey)
-> (VerificationKey GenesisKey -> ByteString)
-> (AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey))
-> SerialiseAsCBOR (VerificationKey GenesisKey)
AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey)
VerificationKey GenesisKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey)
serialiseToCBOR :: VerificationKey GenesisKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisKey)
SerialiseAsCBOR
newtype SigningKey GenesisKey =
GenesisSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisKey -> ShowS
[SigningKey GenesisKey] -> ShowS
SigningKey GenesisKey -> String
(Int -> SigningKey GenesisKey -> ShowS)
-> (SigningKey GenesisKey -> String)
-> ([SigningKey GenesisKey] -> ShowS)
-> Show (SigningKey GenesisKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisKey] -> ShowS
$cshowList :: [SigningKey GenesisKey] -> ShowS
show :: SigningKey GenesisKey -> String
$cshow :: SigningKey GenesisKey -> String
showsPrec :: Int -> SigningKey GenesisKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisKey -> ShowS
Show, String -> SigningKey GenesisKey
(String -> SigningKey GenesisKey)
-> IsString (SigningKey GenesisKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisKey
$cfromString :: String -> SigningKey GenesisKey
IsString) via UsingRawBytesHex (SigningKey GenesisKey)
deriving newtype (Typeable (SigningKey GenesisKey)
Typeable (SigningKey GenesisKey)
-> (SigningKey GenesisKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size)
-> ToCBOR (SigningKey GenesisKey)
SigningKey GenesisKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size
toCBOR :: SigningKey GenesisKey -> Encoding
$ctoCBOR :: SigningKey GenesisKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey GenesisKey)
ToCBOR, Typeable (SigningKey GenesisKey)
Decoder s (SigningKey GenesisKey)
Typeable (SigningKey GenesisKey)
-> (forall s. Decoder s (SigningKey GenesisKey))
-> (Proxy (SigningKey GenesisKey) -> Text)
-> FromCBOR (SigningKey GenesisKey)
Proxy (SigningKey GenesisKey) -> Text
forall s. Decoder s (SigningKey GenesisKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey GenesisKey) -> Text
$clabel :: Proxy (SigningKey GenesisKey) -> Text
fromCBOR :: Decoder s (SigningKey GenesisKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisKey)
$cp1FromCBOR :: Typeable (SigningKey GenesisKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey GenesisKey)
HasTypeProxy (SigningKey GenesisKey)
-> (SigningKey GenesisKey -> ByteString)
-> (AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey))
-> SerialiseAsCBOR (SigningKey GenesisKey)
AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey)
SigningKey GenesisKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey)
serialiseToCBOR :: SigningKey GenesisKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisKey -> Crypto.Seed -> SigningKey GenesisKey
deterministicSigningKey :: AsType GenesisKey -> Seed -> SigningKey GenesisKey
deterministicSigningKey AsType GenesisKey
AsGenesisKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisKey
GenesisSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisKey -> Word
deterministicSigningKeySeedSize AsType GenesisKey
AsGenesisKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey
getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey
getVerificationKey (GenesisSigningKey sk) =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey
GenesisVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Genesis StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey
verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey
verificationKeyHash (GenesisVerificationKey vkey) =
KeyHash 'Genesis StandardCrypto -> Hash GenesisKey
GenesisKeyHash (VKey 'Genesis StandardCrypto -> KeyHash 'Genesis StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Genesis StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisKey) where
serialiseToRawBytes :: VerificationKey GenesisKey -> ByteString
serialiseToRawBytes (GenesisVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisKey)
-> ByteString -> Maybe (VerificationKey GenesisKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisKey) ByteString
bs =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey
GenesisVerificationKey (VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey GenesisKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey GenesisKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey GenesisKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisKey) where
serialiseToRawBytes :: SigningKey GenesisKey -> ByteString
serialiseToRawBytes (GenesisSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisKey)
-> ByteString -> Maybe (SigningKey GenesisKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisKey
GenesisSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey GenesisKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisKey =
GenesisKeyHash (Sophie.KeyHash Sophie.Genesis StandardCrypto)
deriving stock (Hash GenesisKey -> Hash GenesisKey -> Bool
(Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> Eq (Hash GenesisKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c/= :: Hash GenesisKey -> Hash GenesisKey -> Bool
== :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c== :: Hash GenesisKey -> Hash GenesisKey -> Bool
Eq, Eq (Hash GenesisKey)
Eq (Hash GenesisKey)
-> (Hash GenesisKey -> Hash GenesisKey -> Ordering)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey)
-> (Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey)
-> Ord (Hash GenesisKey)
Hash GenesisKey -> Hash GenesisKey -> Bool
Hash GenesisKey -> Hash GenesisKey -> Ordering
Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
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
min :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
$cmin :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
max :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
$cmax :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
>= :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c>= :: Hash GenesisKey -> Hash GenesisKey -> Bool
> :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c> :: Hash GenesisKey -> Hash GenesisKey -> Bool
<= :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c<= :: Hash GenesisKey -> Hash GenesisKey -> Bool
< :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c< :: Hash GenesisKey -> Hash GenesisKey -> Bool
compare :: Hash GenesisKey -> Hash GenesisKey -> Ordering
$ccompare :: Hash GenesisKey -> Hash GenesisKey -> Ordering
$cp1Ord :: Eq (Hash GenesisKey)
Ord)
deriving (Int -> Hash GenesisKey -> ShowS
[Hash GenesisKey] -> ShowS
Hash GenesisKey -> String
(Int -> Hash GenesisKey -> ShowS)
-> (Hash GenesisKey -> String)
-> ([Hash GenesisKey] -> ShowS)
-> Show (Hash GenesisKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisKey] -> ShowS
$cshowList :: [Hash GenesisKey] -> ShowS
show :: Hash GenesisKey -> String
$cshow :: Hash GenesisKey -> String
showsPrec :: Int -> Hash GenesisKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisKey -> ShowS
Show, String -> Hash GenesisKey
(String -> Hash GenesisKey) -> IsString (Hash GenesisKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisKey
$cfromString :: String -> Hash GenesisKey
IsString) via UsingRawBytesHex (Hash GenesisKey)
deriving (Typeable (Hash GenesisKey)
Typeable (Hash GenesisKey)
-> (Hash GenesisKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size)
-> ToCBOR (Hash GenesisKey)
Hash GenesisKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size
toCBOR :: Hash GenesisKey -> Encoding
$ctoCBOR :: Hash GenesisKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisKey)
ToCBOR, Typeable (Hash GenesisKey)
Decoder s (Hash GenesisKey)
Typeable (Hash GenesisKey)
-> (forall s. Decoder s (Hash GenesisKey))
-> (Proxy (Hash GenesisKey) -> Text)
-> FromCBOR (Hash GenesisKey)
Proxy (Hash GenesisKey) -> Text
forall s. Decoder s (Hash GenesisKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisKey) -> Text
$clabel :: Proxy (Hash GenesisKey) -> Text
fromCBOR :: Decoder s (Hash GenesisKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisKey)
$cp1FromCBOR :: Typeable (Hash GenesisKey)
FromCBOR) via UsingRawBytes (Hash GenesisKey)
deriving anyclass HasTypeProxy (Hash GenesisKey)
HasTypeProxy (Hash GenesisKey)
-> (Hash GenesisKey -> ByteString)
-> (AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey))
-> SerialiseAsCBOR (Hash GenesisKey)
AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey)
Hash GenesisKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey)
serialiseToCBOR :: Hash GenesisKey -> ByteString
$cserialiseToCBOR :: Hash GenesisKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisKey) where
serialiseToRawBytes :: Hash GenesisKey -> ByteString
serialiseToRawBytes (GenesisKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisKey) -> ByteString -> Maybe (Hash GenesisKey)
deserialiseFromRawBytes (AsHash AsGenesisKey) ByteString
bs =
KeyHash 'Genesis StandardCrypto -> Hash GenesisKey
GenesisKeyHash (KeyHash 'Genesis StandardCrypto -> Hash GenesisKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Genesis StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Genesis StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> Hash GenesisKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisKey) where
textEnvelopeType :: AsType (VerificationKey GenesisKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisKey)
_ = TextEnvelopeType
"GenesisVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisKey) where
textEnvelopeType :: AsType (SigningKey GenesisKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisKey)
_ = TextEnvelopeType
"GenesisSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
data GenesisExtendedKey
instance HasTypeProxy GenesisExtendedKey where
data AsType GenesisExtendedKey = AsGenesisExtendedKey
proxyToAsType :: Proxy GenesisExtendedKey -> AsType GenesisExtendedKey
proxyToAsType Proxy GenesisExtendedKey
_ = AsType GenesisExtendedKey
AsGenesisExtendedKey
instance Key GenesisExtendedKey where
newtype VerificationKey GenesisExtendedKey =
GenesisExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
(VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool)
-> (VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool)
-> Eq (VerificationKey GenesisExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
$c/= :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
== :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
$c== :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey GenesisExtendedKey)
HasTypeProxy (VerificationKey GenesisExtendedKey)
-> (VerificationKey GenesisExtendedKey -> ByteString)
-> (AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey))
-> SerialiseAsCBOR (VerificationKey GenesisExtendedKey)
AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey)
VerificationKey GenesisExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey)
serialiseToCBOR :: VerificationKey GenesisExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey GenesisExtendedKey -> ShowS
[VerificationKey GenesisExtendedKey] -> ShowS
VerificationKey GenesisExtendedKey -> String
(Int -> VerificationKey GenesisExtendedKey -> ShowS)
-> (VerificationKey GenesisExtendedKey -> String)
-> ([VerificationKey GenesisExtendedKey] -> ShowS)
-> Show (VerificationKey GenesisExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisExtendedKey] -> ShowS
$cshowList :: [VerificationKey GenesisExtendedKey] -> ShowS
show :: VerificationKey GenesisExtendedKey -> String
$cshow :: VerificationKey GenesisExtendedKey -> String
showsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS
Show, String -> VerificationKey GenesisExtendedKey
(String -> VerificationKey GenesisExtendedKey)
-> IsString (VerificationKey GenesisExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisExtendedKey
$cfromString :: String -> VerificationKey GenesisExtendedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisExtendedKey)
newtype SigningKey GenesisExtendedKey =
GenesisExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey GenesisExtendedKey)
HasTypeProxy (SigningKey GenesisExtendedKey)
-> (SigningKey GenesisExtendedKey -> ByteString)
-> (AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey))
-> SerialiseAsCBOR (SigningKey GenesisExtendedKey)
AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey)
SigningKey GenesisExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey)
serialiseToCBOR :: SigningKey GenesisExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey GenesisExtendedKey -> ShowS
[SigningKey GenesisExtendedKey] -> ShowS
SigningKey GenesisExtendedKey -> String
(Int -> SigningKey GenesisExtendedKey -> ShowS)
-> (SigningKey GenesisExtendedKey -> String)
-> ([SigningKey GenesisExtendedKey] -> ShowS)
-> Show (SigningKey GenesisExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisExtendedKey] -> ShowS
$cshowList :: [SigningKey GenesisExtendedKey] -> ShowS
show :: SigningKey GenesisExtendedKey -> String
$cshow :: SigningKey GenesisExtendedKey -> String
showsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS
Show, String -> SigningKey GenesisExtendedKey
(String -> SigningKey GenesisExtendedKey)
-> IsString (SigningKey GenesisExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisExtendedKey
$cfromString :: String -> SigningKey GenesisExtendedKey
IsString) via UsingRawBytesHex (SigningKey GenesisExtendedKey)
deterministicSigningKey :: AsType GenesisExtendedKey
-> Crypto.Seed
-> SigningKey GenesisExtendedKey
deterministicSigningKey :: AsType GenesisExtendedKey -> Seed -> SigningKey GenesisExtendedKey
deterministicSigningKey AsType GenesisExtendedKey
AsGenesisExtendedKey Seed
seed =
XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word
deterministicSigningKeySeedSize AsType GenesisExtendedKey
AsGenesisExtendedKey = Word
32
getVerificationKey :: SigningKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey
getVerificationKey :: SigningKey GenesisExtendedKey -> VerificationKey GenesisExtendedKey
getVerificationKey (GenesisExtendedSigningKey sk) =
XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey GenesisExtendedKey
-> Hash GenesisExtendedKey
verificationKeyHash :: VerificationKey GenesisExtendedKey -> Hash GenesisExtendedKey
verificationKeyHash (GenesisExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto -> Hash GenesisExtendedKey
GenesisExtendedKeyHash
(KeyHash 'Staking StandardCrypto -> Hash GenesisExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash GenesisExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash GenesisExtendedKey)
-> Hash Blake2b_224 XPub -> Hash GenesisExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey GenesisExtendedKey) where
toCBOR :: VerificationKey GenesisExtendedKey -> Encoding
toCBOR (GenesisExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey GenesisExtendedKey) where
fromCBOR :: Decoder s (VerificationKey GenesisExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey GenesisExtendedKey))
-> (XPub -> Decoder s (VerificationKey GenesisExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey GenesisExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey GenesisExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey GenesisExtendedKey
-> Decoder s (VerificationKey GenesisExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey GenesisExtendedKey
-> Decoder s (VerificationKey GenesisExtendedKey))
-> (XPub -> VerificationKey GenesisExtendedKey)
-> XPub
-> Decoder s (VerificationKey GenesisExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey GenesisExtendedKey) where
toCBOR :: SigningKey GenesisExtendedKey -> Encoding
toCBOR (GenesisExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey GenesisExtendedKey) where
fromCBOR :: Decoder s (SigningKey GenesisExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey GenesisExtendedKey))
-> (XPrv -> Decoder s (SigningKey GenesisExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey GenesisExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey GenesisExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey GenesisExtendedKey
-> Decoder s (SigningKey GenesisExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey GenesisExtendedKey
-> Decoder s (SigningKey GenesisExtendedKey))
-> (XPrv -> SigningKey GenesisExtendedKey)
-> XPrv
-> Decoder s (SigningKey GenesisExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) where
serialiseToRawBytes :: VerificationKey GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey GenesisExtendedKey)
-> ByteString -> Maybe (VerificationKey GenesisExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey GenesisExtendedKey))
-> (XPub -> Maybe (VerificationKey GenesisExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey GenesisExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey GenesisExtendedKey)
-> String -> Maybe (VerificationKey GenesisExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey GenesisExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey GenesisExtendedKey
-> Maybe (VerificationKey GenesisExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey GenesisExtendedKey
-> Maybe (VerificationKey GenesisExtendedKey))
-> (XPub -> VerificationKey GenesisExtendedKey)
-> XPub
-> Maybe (VerificationKey GenesisExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey GenesisExtendedKey) where
serialiseToRawBytes :: SigningKey GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey GenesisExtendedKey)
-> ByteString -> Maybe (SigningKey GenesisExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey GenesisExtendedKey))
-> (XPrv -> Maybe (SigningKey GenesisExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey GenesisExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey GenesisExtendedKey)
-> String -> Maybe (SigningKey GenesisExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey GenesisExtendedKey)
forall a. Maybe a
Nothing) (SigningKey GenesisExtendedKey
-> Maybe (SigningKey GenesisExtendedKey)
forall a. a -> Maybe a
Just (SigningKey GenesisExtendedKey
-> Maybe (SigningKey GenesisExtendedKey))
-> (XPrv -> SigningKey GenesisExtendedKey)
-> XPrv
-> Maybe (SigningKey GenesisExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
newtype instance Hash GenesisExtendedKey =
GenesisExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
(Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> Eq (Hash GenesisExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c/= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
== :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c== :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
Eq, Eq (Hash GenesisExtendedKey)
Eq (Hash GenesisExtendedKey)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey)
-> (Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey)
-> Ord (Hash GenesisExtendedKey)
Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering
Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
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
min :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
$cmin :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
max :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
$cmax :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
>= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c>= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
> :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c> :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
<= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c<= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
< :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c< :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
compare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering
$ccompare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering
$cp1Ord :: Eq (Hash GenesisExtendedKey)
Ord)
deriving (Int -> Hash GenesisExtendedKey -> ShowS
[Hash GenesisExtendedKey] -> ShowS
Hash GenesisExtendedKey -> String
(Int -> Hash GenesisExtendedKey -> ShowS)
-> (Hash GenesisExtendedKey -> String)
-> ([Hash GenesisExtendedKey] -> ShowS)
-> Show (Hash GenesisExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisExtendedKey] -> ShowS
$cshowList :: [Hash GenesisExtendedKey] -> ShowS
show :: Hash GenesisExtendedKey -> String
$cshow :: Hash GenesisExtendedKey -> String
showsPrec :: Int -> Hash GenesisExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisExtendedKey -> ShowS
Show, String -> Hash GenesisExtendedKey
(String -> Hash GenesisExtendedKey)
-> IsString (Hash GenesisExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisExtendedKey
$cfromString :: String -> Hash GenesisExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisExtendedKey)
deriving (Typeable (Hash GenesisExtendedKey)
Typeable (Hash GenesisExtendedKey)
-> (Hash GenesisExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size)
-> ToCBOR (Hash GenesisExtendedKey)
Hash GenesisExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size
toCBOR :: Hash GenesisExtendedKey -> Encoding
$ctoCBOR :: Hash GenesisExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisExtendedKey)
ToCBOR, Typeable (Hash GenesisExtendedKey)
Decoder s (Hash GenesisExtendedKey)
Typeable (Hash GenesisExtendedKey)
-> (forall s. Decoder s (Hash GenesisExtendedKey))
-> (Proxy (Hash GenesisExtendedKey) -> Text)
-> FromCBOR (Hash GenesisExtendedKey)
Proxy (Hash GenesisExtendedKey) -> Text
forall s. Decoder s (Hash GenesisExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisExtendedKey) -> Text
$clabel :: Proxy (Hash GenesisExtendedKey) -> Text
fromCBOR :: Decoder s (Hash GenesisExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisExtendedKey)
$cp1FromCBOR :: Typeable (Hash GenesisExtendedKey)
FromCBOR) via UsingRawBytes (Hash GenesisExtendedKey)
deriving anyclass HasTypeProxy (Hash GenesisExtendedKey)
HasTypeProxy (Hash GenesisExtendedKey)
-> (Hash GenesisExtendedKey -> ByteString)
-> (AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey))
-> SerialiseAsCBOR (Hash GenesisExtendedKey)
AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey)
Hash GenesisExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey)
serialiseToCBOR :: Hash GenesisExtendedKey -> ByteString
$cserialiseToCBOR :: Hash GenesisExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisExtendedKey) where
serialiseToRawBytes :: Hash GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisExtendedKey)
-> ByteString -> Maybe (Hash GenesisExtendedKey)
deserialiseFromRawBytes (AsHash AsGenesisExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash GenesisExtendedKey
GenesisExtendedKeyHash (KeyHash 'Staking StandardCrypto -> Hash GenesisExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisExtendedKey) where
textEnvelopeType :: AsType (VerificationKey GenesisExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisExtendedKey)
_ = TextEnvelopeType
"GenesisExtendedVerificationKey_ed25519_bip32"
instance HasTextEnvelope (SigningKey GenesisExtendedKey) where
textEnvelopeType :: AsType (SigningKey GenesisExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisExtendedKey)
_ = TextEnvelopeType
"GenesisExtendedSigningKey_ed25519_bip32"
instance CastVerificationKeyRole GenesisExtendedKey GenesisKey where
castVerificationKey :: VerificationKey GenesisExtendedKey -> VerificationKey GenesisKey
castVerificationKey (GenesisExtendedVerificationKey vk) =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey
GenesisVerificationKey
(VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey)
-> (XPub -> VKey 'Genesis StandardCrypto)
-> XPub
-> VerificationKey GenesisKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'Genesis StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey GenesisKey)
-> XPub -> VerificationKey GenesisKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data GenesisDelegateKey
instance HasTypeProxy GenesisDelegateKey where
data AsType GenesisDelegateKey = AsGenesisDelegateKey
proxyToAsType :: Proxy GenesisDelegateKey -> AsType GenesisDelegateKey
proxyToAsType Proxy GenesisDelegateKey
_ = AsType GenesisDelegateKey
AsGenesisDelegateKey
instance Key GenesisDelegateKey where
newtype VerificationKey GenesisDelegateKey =
GenesisDelegateVerificationKey (Sophie.VKey Sophie.GenesisDelegate StandardCrypto)
deriving stock (VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
(VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool)
-> (VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool)
-> Eq (VerificationKey GenesisDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
$c/= :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
== :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
$c== :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
Eq)
deriving (Int -> VerificationKey GenesisDelegateKey -> ShowS
[VerificationKey GenesisDelegateKey] -> ShowS
VerificationKey GenesisDelegateKey -> String
(Int -> VerificationKey GenesisDelegateKey -> ShowS)
-> (VerificationKey GenesisDelegateKey -> String)
-> ([VerificationKey GenesisDelegateKey] -> ShowS)
-> Show (VerificationKey GenesisDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisDelegateKey] -> ShowS
$cshowList :: [VerificationKey GenesisDelegateKey] -> ShowS
show :: VerificationKey GenesisDelegateKey -> String
$cshow :: VerificationKey GenesisDelegateKey -> String
showsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS
Show, String -> VerificationKey GenesisDelegateKey
(String -> VerificationKey GenesisDelegateKey)
-> IsString (VerificationKey GenesisDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisDelegateKey
$cfromString :: String -> VerificationKey GenesisDelegateKey
IsString) via UsingRawBytesHex (VerificationKey GenesisDelegateKey)
deriving newtype (Typeable (VerificationKey GenesisDelegateKey)
Typeable (VerificationKey GenesisDelegateKey)
-> (VerificationKey GenesisDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size)
-> ToCBOR (VerificationKey GenesisDelegateKey)
VerificationKey GenesisDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size
toCBOR :: VerificationKey GenesisDelegateKey -> Encoding
$ctoCBOR :: VerificationKey GenesisDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey GenesisDelegateKey)
ToCBOR, Typeable (VerificationKey GenesisDelegateKey)
Decoder s (VerificationKey GenesisDelegateKey)
Typeable (VerificationKey GenesisDelegateKey)
-> (forall s. Decoder s (VerificationKey GenesisDelegateKey))
-> (Proxy (VerificationKey GenesisDelegateKey) -> Text)
-> FromCBOR (VerificationKey GenesisDelegateKey)
Proxy (VerificationKey GenesisDelegateKey) -> Text
forall s. Decoder s (VerificationKey GenesisDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey GenesisDelegateKey) -> Text
$clabel :: Proxy (VerificationKey GenesisDelegateKey) -> Text
fromCBOR :: Decoder s (VerificationKey GenesisDelegateKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisDelegateKey)
$cp1FromCBOR :: Typeable (VerificationKey GenesisDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey GenesisDelegateKey)
HasTypeProxy (VerificationKey GenesisDelegateKey)
-> (VerificationKey GenesisDelegateKey -> ByteString)
-> (AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey))
-> SerialiseAsCBOR (VerificationKey GenesisDelegateKey)
AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey)
VerificationKey GenesisDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey)
serialiseToCBOR :: VerificationKey GenesisDelegateKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisDelegateKey)
SerialiseAsCBOR
newtype SigningKey GenesisDelegateKey =
GenesisDelegateSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisDelegateKey -> ShowS
[SigningKey GenesisDelegateKey] -> ShowS
SigningKey GenesisDelegateKey -> String
(Int -> SigningKey GenesisDelegateKey -> ShowS)
-> (SigningKey GenesisDelegateKey -> String)
-> ([SigningKey GenesisDelegateKey] -> ShowS)
-> Show (SigningKey GenesisDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisDelegateKey] -> ShowS
$cshowList :: [SigningKey GenesisDelegateKey] -> ShowS
show :: SigningKey GenesisDelegateKey -> String
$cshow :: SigningKey GenesisDelegateKey -> String
showsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS
Show, String -> SigningKey GenesisDelegateKey
(String -> SigningKey GenesisDelegateKey)
-> IsString (SigningKey GenesisDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisDelegateKey
$cfromString :: String -> SigningKey GenesisDelegateKey
IsString) via UsingRawBytesHex (SigningKey GenesisDelegateKey)
deriving newtype (Typeable (SigningKey GenesisDelegateKey)
Typeable (SigningKey GenesisDelegateKey)
-> (SigningKey GenesisDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size)
-> ToCBOR (SigningKey GenesisDelegateKey)
SigningKey GenesisDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size
toCBOR :: SigningKey GenesisDelegateKey -> Encoding
$ctoCBOR :: SigningKey GenesisDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey GenesisDelegateKey)
ToCBOR, Typeable (SigningKey GenesisDelegateKey)
Decoder s (SigningKey GenesisDelegateKey)
Typeable (SigningKey GenesisDelegateKey)
-> (forall s. Decoder s (SigningKey GenesisDelegateKey))
-> (Proxy (SigningKey GenesisDelegateKey) -> Text)
-> FromCBOR (SigningKey GenesisDelegateKey)
Proxy (SigningKey GenesisDelegateKey) -> Text
forall s. Decoder s (SigningKey GenesisDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey GenesisDelegateKey) -> Text
$clabel :: Proxy (SigningKey GenesisDelegateKey) -> Text
fromCBOR :: Decoder s (SigningKey GenesisDelegateKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisDelegateKey)
$cp1FromCBOR :: Typeable (SigningKey GenesisDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey GenesisDelegateKey)
HasTypeProxy (SigningKey GenesisDelegateKey)
-> (SigningKey GenesisDelegateKey -> ByteString)
-> (AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey))
-> SerialiseAsCBOR (SigningKey GenesisDelegateKey)
AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey)
SigningKey GenesisDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey)
serialiseToCBOR :: SigningKey GenesisDelegateKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisDelegateKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisDelegateKey -> Crypto.Seed -> SigningKey GenesisDelegateKey
deterministicSigningKey :: AsType GenesisDelegateKey -> Seed -> SigningKey GenesisDelegateKey
deterministicSigningKey AsType GenesisDelegateKey
AsGenesisDelegateKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisDelegateKey
GenesisDelegateSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word
deterministicSigningKeySeedSize AsType GenesisDelegateKey
AsGenesisDelegateKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey
getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey
getVerificationKey (GenesisDelegateSigningKey sk) =
VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'GenesisDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey
verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey
verificationKeyHash (GenesisDelegateVerificationKey vkey) =
KeyHash 'GenesisDelegate StandardCrypto -> Hash GenesisDelegateKey
GenesisDelegateKeyHash (VKey 'GenesisDelegate StandardCrypto
-> KeyHash 'GenesisDelegate StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'GenesisDelegate StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) where
serialiseToRawBytes :: VerificationKey GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString -> Maybe (VerificationKey GenesisDelegateKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisDelegateKey) ByteString
bs =
VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey (VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey)
-> (VerKeyDSIGN Ed25519DSIGN
-> VKey 'GenesisDelegate StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey GenesisDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'GenesisDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey GenesisDelegateKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey GenesisDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisDelegateKey) where
serialiseToRawBytes :: SigningKey GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisDelegateKey)
-> ByteString -> Maybe (SigningKey GenesisDelegateKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisDelegateKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisDelegateKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisDelegateKey
GenesisDelegateSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisDelegateKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey GenesisDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisDelegateKey =
GenesisDelegateKeyHash (Sophie.KeyHash Sophie.GenesisDelegate StandardCrypto)
deriving stock (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
(Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> Eq (Hash GenesisDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c/= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
== :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c== :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
Eq, Eq (Hash GenesisDelegateKey)
Eq (Hash GenesisDelegateKey)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey)
-> (Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey)
-> Ord (Hash GenesisDelegateKey)
Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering
Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
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
min :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
$cmin :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
max :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
$cmax :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
>= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c>= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
> :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c> :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
<= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c<= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
< :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c< :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
compare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering
$ccompare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering
$cp1Ord :: Eq (Hash GenesisDelegateKey)
Ord)
deriving (Int -> Hash GenesisDelegateKey -> ShowS
[Hash GenesisDelegateKey] -> ShowS
Hash GenesisDelegateKey -> String
(Int -> Hash GenesisDelegateKey -> ShowS)
-> (Hash GenesisDelegateKey -> String)
-> ([Hash GenesisDelegateKey] -> ShowS)
-> Show (Hash GenesisDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisDelegateKey] -> ShowS
$cshowList :: [Hash GenesisDelegateKey] -> ShowS
show :: Hash GenesisDelegateKey -> String
$cshow :: Hash GenesisDelegateKey -> String
showsPrec :: Int -> Hash GenesisDelegateKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisDelegateKey -> ShowS
Show, String -> Hash GenesisDelegateKey
(String -> Hash GenesisDelegateKey)
-> IsString (Hash GenesisDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisDelegateKey
$cfromString :: String -> Hash GenesisDelegateKey
IsString) via UsingRawBytesHex (Hash GenesisDelegateKey)
deriving (Typeable (Hash GenesisDelegateKey)
Typeable (Hash GenesisDelegateKey)
-> (Hash GenesisDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size)
-> ToCBOR (Hash GenesisDelegateKey)
Hash GenesisDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size
toCBOR :: Hash GenesisDelegateKey -> Encoding
$ctoCBOR :: Hash GenesisDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisDelegateKey)
ToCBOR, Typeable (Hash GenesisDelegateKey)
Decoder s (Hash GenesisDelegateKey)
Typeable (Hash GenesisDelegateKey)
-> (forall s. Decoder s (Hash GenesisDelegateKey))
-> (Proxy (Hash GenesisDelegateKey) -> Text)
-> FromCBOR (Hash GenesisDelegateKey)
Proxy (Hash GenesisDelegateKey) -> Text
forall s. Decoder s (Hash GenesisDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisDelegateKey) -> Text
$clabel :: Proxy (Hash GenesisDelegateKey) -> Text
fromCBOR :: Decoder s (Hash GenesisDelegateKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisDelegateKey)
$cp1FromCBOR :: Typeable (Hash GenesisDelegateKey)
FromCBOR) via UsingRawBytes (Hash GenesisDelegateKey)
deriving anyclass HasTypeProxy (Hash GenesisDelegateKey)
HasTypeProxy (Hash GenesisDelegateKey)
-> (Hash GenesisDelegateKey -> ByteString)
-> (AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey))
-> SerialiseAsCBOR (Hash GenesisDelegateKey)
AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey)
Hash GenesisDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey)
serialiseToCBOR :: Hash GenesisDelegateKey -> ByteString
$cserialiseToCBOR :: Hash GenesisDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisDelegateKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisDelegateKey) where
serialiseToRawBytes :: Hash GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisDelegateKey)
-> ByteString -> Maybe (Hash GenesisDelegateKey)
deserialiseFromRawBytes (AsHash AsGenesisDelegateKey) ByteString
bs =
KeyHash 'GenesisDelegate StandardCrypto -> Hash GenesisDelegateKey
GenesisDelegateKeyHash (KeyHash 'GenesisDelegate StandardCrypto
-> Hash GenesisDelegateKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'GenesisDelegate StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'GenesisDelegate StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisDelegateKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisDelegateKey) where
textEnvelopeType :: AsType (VerificationKey GenesisDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisDelegateKey)
_ = TextEnvelopeType
"GenesisDelegateVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisDelegateKey) where
textEnvelopeType :: AsType (SigningKey GenesisDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisDelegateKey)
_ = TextEnvelopeType
"GenesisDelegateSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole GenesisDelegateKey StakePoolKey where
castVerificationKey :: VerificationKey GenesisDelegateKey -> VerificationKey StakePoolKey
castVerificationKey (GenesisDelegateVerificationKey (Sophie.VKey vkey)) =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'StakePool StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole GenesisDelegateKey StakePoolKey where
castSigningKey :: SigningKey GenesisDelegateKey -> SigningKey StakePoolKey
castSigningKey (GenesisDelegateSigningKey skey) =
SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
StakePoolSigningKey SignKeyDSIGN StandardCrypto
skey
data GenesisDelegateExtendedKey
instance HasTypeProxy GenesisDelegateExtendedKey where
data AsType GenesisDelegateExtendedKey = AsGenesisDelegateExtendedKey
proxyToAsType :: Proxy GenesisDelegateExtendedKey
-> AsType GenesisDelegateExtendedKey
proxyToAsType Proxy GenesisDelegateExtendedKey
_ = AsType GenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey
instance Key GenesisDelegateExtendedKey where
newtype VerificationKey GenesisDelegateExtendedKey =
GenesisDelegateExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
(VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool)
-> (VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool)
-> Eq (VerificationKey GenesisDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
$c/= :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
== :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
$c== :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey GenesisDelegateExtendedKey)
HasTypeProxy (VerificationKey GenesisDelegateExtendedKey)
-> (VerificationKey GenesisDelegateExtendedKey -> ByteString)
-> (AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (VerificationKey GenesisDelegateExtendedKey))
-> SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey)
AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateExtendedKey)
VerificationKey GenesisDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateExtendedKey)
serialiseToCBOR :: VerificationKey GenesisDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisDelegateExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
[VerificationKey GenesisDelegateExtendedKey] -> ShowS
VerificationKey GenesisDelegateExtendedKey -> String
(Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS)
-> (VerificationKey GenesisDelegateExtendedKey -> String)
-> ([VerificationKey GenesisDelegateExtendedKey] -> ShowS)
-> Show (VerificationKey GenesisDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS
$cshowList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS
show :: VerificationKey GenesisDelegateExtendedKey -> String
$cshow :: VerificationKey GenesisDelegateExtendedKey -> String
showsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
Show, String -> VerificationKey GenesisDelegateExtendedKey
(String -> VerificationKey GenesisDelegateExtendedKey)
-> IsString (VerificationKey GenesisDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisDelegateExtendedKey
$cfromString :: String -> VerificationKey GenesisDelegateExtendedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisDelegateExtendedKey)
newtype SigningKey GenesisDelegateExtendedKey =
GenesisDelegateExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey GenesisDelegateExtendedKey)
HasTypeProxy (SigningKey GenesisDelegateExtendedKey)
-> (SigningKey GenesisDelegateExtendedKey -> ByteString)
-> (AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey))
-> SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey)
AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey)
SigningKey GenesisDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey)
serialiseToCBOR :: SigningKey GenesisDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisDelegateExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
[SigningKey GenesisDelegateExtendedKey] -> ShowS
SigningKey GenesisDelegateExtendedKey -> String
(Int -> SigningKey GenesisDelegateExtendedKey -> ShowS)
-> (SigningKey GenesisDelegateExtendedKey -> String)
-> ([SigningKey GenesisDelegateExtendedKey] -> ShowS)
-> Show (SigningKey GenesisDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS
$cshowList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS
show :: SigningKey GenesisDelegateExtendedKey -> String
$cshow :: SigningKey GenesisDelegateExtendedKey -> String
showsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
Show, String -> SigningKey GenesisDelegateExtendedKey
(String -> SigningKey GenesisDelegateExtendedKey)
-> IsString (SigningKey GenesisDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisDelegateExtendedKey
$cfromString :: String -> SigningKey GenesisDelegateExtendedKey
IsString) via UsingRawBytesHex (SigningKey GenesisDelegateExtendedKey)
deterministicSigningKey :: AsType GenesisDelegateExtendedKey
-> Crypto.Seed
-> SigningKey GenesisDelegateExtendedKey
deterministicSigningKey :: AsType GenesisDelegateExtendedKey
-> Seed -> SigningKey GenesisDelegateExtendedKey
deterministicSigningKey AsType GenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey Seed
seed =
XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word
deterministicSigningKeySeedSize AsType GenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey = Word
32
getVerificationKey :: SigningKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey
getVerificationKey :: SigningKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey
getVerificationKey (GenesisDelegateExtendedSigningKey sk) =
XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
verificationKeyHash (GenesisDelegateExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto -> Hash GenesisDelegateExtendedKey
GenesisDelegateExtendedKeyHash
(KeyHash 'Staking StandardCrypto
-> Hash GenesisDelegateExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash GenesisDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash GenesisDelegateExtendedKey)
-> Hash Blake2b_224 XPub -> Hash GenesisDelegateExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey GenesisDelegateExtendedKey) where
toCBOR :: VerificationKey GenesisDelegateExtendedKey -> Encoding
toCBOR (GenesisDelegateExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey GenesisDelegateExtendedKey) where
fromCBOR :: Decoder s (VerificationKey GenesisDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey GenesisDelegateExtendedKey))
-> (XPub -> Decoder s (VerificationKey GenesisDelegateExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey GenesisDelegateExtendedKey
-> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey GenesisDelegateExtendedKey
-> Decoder s (VerificationKey GenesisDelegateExtendedKey))
-> (XPub -> VerificationKey GenesisDelegateExtendedKey)
-> XPub
-> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey GenesisDelegateExtendedKey) where
toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding
toCBOR (GenesisDelegateExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey GenesisDelegateExtendedKey) where
fromCBOR :: Decoder s (SigningKey GenesisDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey GenesisDelegateExtendedKey))
-> (XPrv -> Decoder s (SigningKey GenesisDelegateExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey GenesisDelegateExtendedKey
-> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey GenesisDelegateExtendedKey
-> Decoder s (SigningKey GenesisDelegateExtendedKey))
-> (XPrv -> SigningKey GenesisDelegateExtendedKey)
-> XPrv
-> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) where
serialiseToRawBytes :: VerificationKey GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString -> Maybe (VerificationKey GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisDelegateExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey GenesisDelegateExtendedKey))
-> (XPub -> Maybe (VerificationKey GenesisDelegateExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey GenesisDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey GenesisDelegateExtendedKey)
-> String -> Maybe (VerificationKey GenesisDelegateExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey GenesisDelegateExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey GenesisDelegateExtendedKey
-> Maybe (VerificationKey GenesisDelegateExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey GenesisDelegateExtendedKey
-> Maybe (VerificationKey GenesisDelegateExtendedKey))
-> (XPub -> VerificationKey GenesisDelegateExtendedKey)
-> XPub
-> Maybe (VerificationKey GenesisDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) where
serialiseToRawBytes :: SigningKey GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString -> Maybe (SigningKey GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisDelegateExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey GenesisDelegateExtendedKey))
-> (XPrv -> Maybe (SigningKey GenesisDelegateExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey GenesisDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey GenesisDelegateExtendedKey)
-> String -> Maybe (SigningKey GenesisDelegateExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey GenesisDelegateExtendedKey)
forall a. Maybe a
Nothing) (SigningKey GenesisDelegateExtendedKey
-> Maybe (SigningKey GenesisDelegateExtendedKey)
forall a. a -> Maybe a
Just (SigningKey GenesisDelegateExtendedKey
-> Maybe (SigningKey GenesisDelegateExtendedKey))
-> (XPrv -> SigningKey GenesisDelegateExtendedKey)
-> XPrv
-> Maybe (SigningKey GenesisDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
newtype instance Hash GenesisDelegateExtendedKey =
GenesisDelegateExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
(Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool)
-> Eq (Hash GenesisDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c/= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
== :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c== :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
Eq, Eq (Hash GenesisDelegateExtendedKey)
Eq (Hash GenesisDelegateExtendedKey)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey)
-> (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey)
-> Ord (Hash GenesisDelegateExtendedKey)
Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering
Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
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
min :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
$cmin :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
max :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
$cmax :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
>= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c>= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
> :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c> :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
<= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c<= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
< :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c< :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
compare :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering
$ccompare :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering
$cp1Ord :: Eq (Hash GenesisDelegateExtendedKey)
Ord)
deriving (Int -> Hash GenesisDelegateExtendedKey -> ShowS
[Hash GenesisDelegateExtendedKey] -> ShowS
Hash GenesisDelegateExtendedKey -> String
(Int -> Hash GenesisDelegateExtendedKey -> ShowS)
-> (Hash GenesisDelegateExtendedKey -> String)
-> ([Hash GenesisDelegateExtendedKey] -> ShowS)
-> Show (Hash GenesisDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisDelegateExtendedKey] -> ShowS
$cshowList :: [Hash GenesisDelegateExtendedKey] -> ShowS
show :: Hash GenesisDelegateExtendedKey -> String
$cshow :: Hash GenesisDelegateExtendedKey -> String
showsPrec :: Int -> Hash GenesisDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisDelegateExtendedKey -> ShowS
Show, String -> Hash GenesisDelegateExtendedKey
(String -> Hash GenesisDelegateExtendedKey)
-> IsString (Hash GenesisDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisDelegateExtendedKey
$cfromString :: String -> Hash GenesisDelegateExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisDelegateExtendedKey)
deriving (Typeable (Hash GenesisDelegateExtendedKey)
Typeable (Hash GenesisDelegateExtendedKey)
-> (Hash GenesisDelegateExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size)
-> ToCBOR (Hash GenesisDelegateExtendedKey)
Hash GenesisDelegateExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size
toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding
$ctoCBOR :: Hash GenesisDelegateExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisDelegateExtendedKey)
ToCBOR, Typeable (Hash GenesisDelegateExtendedKey)
Decoder s (Hash GenesisDelegateExtendedKey)
Typeable (Hash GenesisDelegateExtendedKey)
-> (forall s. Decoder s (Hash GenesisDelegateExtendedKey))
-> (Proxy (Hash GenesisDelegateExtendedKey) -> Text)
-> FromCBOR (Hash GenesisDelegateExtendedKey)
Proxy (Hash GenesisDelegateExtendedKey) -> Text
forall s. Decoder s (Hash GenesisDelegateExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisDelegateExtendedKey) -> Text
$clabel :: Proxy (Hash GenesisDelegateExtendedKey) -> Text
fromCBOR :: Decoder s (Hash GenesisDelegateExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisDelegateExtendedKey)
$cp1FromCBOR :: Typeable (Hash GenesisDelegateExtendedKey)
FromCBOR) via UsingRawBytes (Hash GenesisDelegateExtendedKey)
deriving anyclass HasTypeProxy (Hash GenesisDelegateExtendedKey)
HasTypeProxy (Hash GenesisDelegateExtendedKey)
-> (Hash GenesisDelegateExtendedKey -> ByteString)
-> (AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey))
-> SerialiseAsCBOR (Hash GenesisDelegateExtendedKey)
AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey)
Hash GenesisDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey)
serialiseToCBOR :: Hash GenesisDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: Hash GenesisDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisDelegateExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) where
serialiseToRawBytes :: Hash GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString -> Maybe (Hash GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsHash AsGenesisDelegateExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash GenesisDelegateExtendedKey
GenesisDelegateExtendedKeyHash (KeyHash 'Staking StandardCrypto
-> Hash GenesisDelegateExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisDelegateExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisDelegateExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) where
textEnvelopeType :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisDelegateExtendedKey)
_ = TextEnvelopeType
"GenesisDelegateExtendedVerificationKey_ed25519_bip32"
instance HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) where
textEnvelopeType :: AsType (SigningKey GenesisDelegateExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisDelegateExtendedKey)
_ = TextEnvelopeType
"GenesisDelegateExtendedSigningKey_ed25519_bip32"
instance CastVerificationKeyRole GenesisDelegateExtendedKey GenesisDelegateKey where
castVerificationKey :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateKey
castVerificationKey (GenesisDelegateExtendedVerificationKey vk) =
VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey
(VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey)
-> (XPub -> VKey 'GenesisDelegate StandardCrypto)
-> XPub
-> VerificationKey GenesisDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'GenesisDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'GenesisDelegate StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'GenesisDelegate StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey GenesisDelegateKey)
-> XPub -> VerificationKey GenesisDelegateKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data GenesisUTxOKey
instance HasTypeProxy GenesisUTxOKey where
data AsType GenesisUTxOKey = AsGenesisUTxOKey
proxyToAsType :: Proxy GenesisUTxOKey -> AsType GenesisUTxOKey
proxyToAsType Proxy GenesisUTxOKey
_ = AsType GenesisUTxOKey
AsGenesisUTxOKey
instance Key GenesisUTxOKey where
newtype VerificationKey GenesisUTxOKey =
GenesisUTxOVerificationKey (Sophie.VKey Sophie.Payment StandardCrypto)
deriving stock (VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
(VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool)
-> (VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool)
-> Eq (VerificationKey GenesisUTxOKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
$c/= :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
== :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
$c== :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
Eq)
deriving (Int -> VerificationKey GenesisUTxOKey -> ShowS
[VerificationKey GenesisUTxOKey] -> ShowS
VerificationKey GenesisUTxOKey -> String
(Int -> VerificationKey GenesisUTxOKey -> ShowS)
-> (VerificationKey GenesisUTxOKey -> String)
-> ([VerificationKey GenesisUTxOKey] -> ShowS)
-> Show (VerificationKey GenesisUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisUTxOKey] -> ShowS
$cshowList :: [VerificationKey GenesisUTxOKey] -> ShowS
show :: VerificationKey GenesisUTxOKey -> String
$cshow :: VerificationKey GenesisUTxOKey -> String
showsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS
Show, String -> VerificationKey GenesisUTxOKey
(String -> VerificationKey GenesisUTxOKey)
-> IsString (VerificationKey GenesisUTxOKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisUTxOKey
$cfromString :: String -> VerificationKey GenesisUTxOKey
IsString) via UsingRawBytesHex (VerificationKey GenesisUTxOKey)
deriving newtype (Typeable (VerificationKey GenesisUTxOKey)
Typeable (VerificationKey GenesisUTxOKey)
-> (VerificationKey GenesisUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size)
-> ToCBOR (VerificationKey GenesisUTxOKey)
VerificationKey GenesisUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size
toCBOR :: VerificationKey GenesisUTxOKey -> Encoding
$ctoCBOR :: VerificationKey GenesisUTxOKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey GenesisUTxOKey)
ToCBOR, Typeable (VerificationKey GenesisUTxOKey)
Decoder s (VerificationKey GenesisUTxOKey)
Typeable (VerificationKey GenesisUTxOKey)
-> (forall s. Decoder s (VerificationKey GenesisUTxOKey))
-> (Proxy (VerificationKey GenesisUTxOKey) -> Text)
-> FromCBOR (VerificationKey GenesisUTxOKey)
Proxy (VerificationKey GenesisUTxOKey) -> Text
forall s. Decoder s (VerificationKey GenesisUTxOKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey GenesisUTxOKey) -> Text
$clabel :: Proxy (VerificationKey GenesisUTxOKey) -> Text
fromCBOR :: Decoder s (VerificationKey GenesisUTxOKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisUTxOKey)
$cp1FromCBOR :: Typeable (VerificationKey GenesisUTxOKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey GenesisUTxOKey)
HasTypeProxy (VerificationKey GenesisUTxOKey)
-> (VerificationKey GenesisUTxOKey -> ByteString)
-> (AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey))
-> SerialiseAsCBOR (VerificationKey GenesisUTxOKey)
AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey)
VerificationKey GenesisUTxOKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey)
serialiseToCBOR :: VerificationKey GenesisUTxOKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisUTxOKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisUTxOKey)
SerialiseAsCBOR
newtype SigningKey GenesisUTxOKey =
GenesisUTxOSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisUTxOKey -> ShowS
[SigningKey GenesisUTxOKey] -> ShowS
SigningKey GenesisUTxOKey -> String
(Int -> SigningKey GenesisUTxOKey -> ShowS)
-> (SigningKey GenesisUTxOKey -> String)
-> ([SigningKey GenesisUTxOKey] -> ShowS)
-> Show (SigningKey GenesisUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisUTxOKey] -> ShowS
$cshowList :: [SigningKey GenesisUTxOKey] -> ShowS
show :: SigningKey GenesisUTxOKey -> String
$cshow :: SigningKey GenesisUTxOKey -> String
showsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS
Show, String -> SigningKey GenesisUTxOKey
(String -> SigningKey GenesisUTxOKey)
-> IsString (SigningKey GenesisUTxOKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisUTxOKey
$cfromString :: String -> SigningKey GenesisUTxOKey
IsString) via UsingRawBytesHex (SigningKey GenesisUTxOKey)
deriving newtype (Typeable (SigningKey GenesisUTxOKey)
Typeable (SigningKey GenesisUTxOKey)
-> (SigningKey GenesisUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size)
-> ToCBOR (SigningKey GenesisUTxOKey)
SigningKey GenesisUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size
toCBOR :: SigningKey GenesisUTxOKey -> Encoding
$ctoCBOR :: SigningKey GenesisUTxOKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey GenesisUTxOKey)
ToCBOR, Typeable (SigningKey GenesisUTxOKey)
Decoder s (SigningKey GenesisUTxOKey)
Typeable (SigningKey GenesisUTxOKey)
-> (forall s. Decoder s (SigningKey GenesisUTxOKey))
-> (Proxy (SigningKey GenesisUTxOKey) -> Text)
-> FromCBOR (SigningKey GenesisUTxOKey)
Proxy (SigningKey GenesisUTxOKey) -> Text
forall s. Decoder s (SigningKey GenesisUTxOKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey GenesisUTxOKey) -> Text
$clabel :: Proxy (SigningKey GenesisUTxOKey) -> Text
fromCBOR :: Decoder s (SigningKey GenesisUTxOKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisUTxOKey)
$cp1FromCBOR :: Typeable (SigningKey GenesisUTxOKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey GenesisUTxOKey)
HasTypeProxy (SigningKey GenesisUTxOKey)
-> (SigningKey GenesisUTxOKey -> ByteString)
-> (AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey))
-> SerialiseAsCBOR (SigningKey GenesisUTxOKey)
AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey)
SigningKey GenesisUTxOKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey)
serialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisUTxOKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisUTxOKey -> Crypto.Seed -> SigningKey GenesisUTxOKey
deterministicSigningKey :: AsType GenesisUTxOKey -> Seed -> SigningKey GenesisUTxOKey
deterministicSigningKey AsType GenesisUTxOKey
AsGenesisUTxOKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisUTxOKey
GenesisUTxOSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word
deterministicSigningKeySeedSize AsType GenesisUTxOKey
AsGenesisUTxOKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey
getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey
getVerificationKey (GenesisUTxOSigningKey sk) =
VKey 'Payment StandardCrypto -> VerificationKey GenesisUTxOKey
GenesisUTxOVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey
verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey
verificationKeyHash (GenesisUTxOVerificationKey vkey) =
KeyHash 'Payment StandardCrypto -> Hash GenesisUTxOKey
GenesisUTxOKeyHash (VKey 'Payment StandardCrypto -> KeyHash 'Payment StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Payment StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) where
serialiseToRawBytes :: VerificationKey GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString -> Maybe (VerificationKey GenesisUTxOKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisUTxOKey) ByteString
bs =
VKey 'Payment StandardCrypto -> VerificationKey GenesisUTxOKey
GenesisUTxOVerificationKey (VKey 'Payment StandardCrypto -> VerificationKey GenesisUTxOKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey GenesisUTxOKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey GenesisUTxOKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey GenesisUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisUTxOKey) where
serialiseToRawBytes :: SigningKey GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Maybe (SigningKey GenesisUTxOKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisUTxOKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisUTxOKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisUTxOKey
GenesisUTxOSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisUTxOKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey GenesisUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisUTxOKey =
GenesisUTxOKeyHash (Sophie.KeyHash Sophie.Payment StandardCrypto)
deriving stock (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
(Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> Eq (Hash GenesisUTxOKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c/= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
== :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c== :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
Eq, Eq (Hash GenesisUTxOKey)
Eq (Hash GenesisUTxOKey)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey
-> Hash GenesisUTxOKey -> Hash GenesisUTxOKey)
-> (Hash GenesisUTxOKey
-> Hash GenesisUTxOKey -> Hash GenesisUTxOKey)
-> Ord (Hash GenesisUTxOKey)
Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering
Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
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
min :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
$cmin :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
max :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
$cmax :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
>= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c>= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
> :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c> :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
<= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c<= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
< :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c< :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
compare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering
$ccompare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering
$cp1Ord :: Eq (Hash GenesisUTxOKey)
Ord)
deriving (Int -> Hash GenesisUTxOKey -> ShowS
[Hash GenesisUTxOKey] -> ShowS
Hash GenesisUTxOKey -> String
(Int -> Hash GenesisUTxOKey -> ShowS)
-> (Hash GenesisUTxOKey -> String)
-> ([Hash GenesisUTxOKey] -> ShowS)
-> Show (Hash GenesisUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisUTxOKey] -> ShowS
$cshowList :: [Hash GenesisUTxOKey] -> ShowS
show :: Hash GenesisUTxOKey -> String
$cshow :: Hash GenesisUTxOKey -> String
showsPrec :: Int -> Hash GenesisUTxOKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisUTxOKey -> ShowS
Show, String -> Hash GenesisUTxOKey
(String -> Hash GenesisUTxOKey) -> IsString (Hash GenesisUTxOKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisUTxOKey
$cfromString :: String -> Hash GenesisUTxOKey
IsString) via UsingRawBytesHex (Hash GenesisUTxOKey)
deriving (Typeable (Hash GenesisUTxOKey)
Typeable (Hash GenesisUTxOKey)
-> (Hash GenesisUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size)
-> ToCBOR (Hash GenesisUTxOKey)
Hash GenesisUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size
toCBOR :: Hash GenesisUTxOKey -> Encoding
$ctoCBOR :: Hash GenesisUTxOKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisUTxOKey)
ToCBOR, Typeable (Hash GenesisUTxOKey)
Decoder s (Hash GenesisUTxOKey)
Typeable (Hash GenesisUTxOKey)
-> (forall s. Decoder s (Hash GenesisUTxOKey))
-> (Proxy (Hash GenesisUTxOKey) -> Text)
-> FromCBOR (Hash GenesisUTxOKey)
Proxy (Hash GenesisUTxOKey) -> Text
forall s. Decoder s (Hash GenesisUTxOKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisUTxOKey) -> Text
$clabel :: Proxy (Hash GenesisUTxOKey) -> Text
fromCBOR :: Decoder s (Hash GenesisUTxOKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisUTxOKey)
$cp1FromCBOR :: Typeable (Hash GenesisUTxOKey)
FromCBOR) via UsingRawBytes (Hash GenesisUTxOKey)
deriving anyclass HasTypeProxy (Hash GenesisUTxOKey)
HasTypeProxy (Hash GenesisUTxOKey)
-> (Hash GenesisUTxOKey -> ByteString)
-> (AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey))
-> SerialiseAsCBOR (Hash GenesisUTxOKey)
AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey)
Hash GenesisUTxOKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey)
serialiseToCBOR :: Hash GenesisUTxOKey -> ByteString
$cserialiseToCBOR :: Hash GenesisUTxOKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisUTxOKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisUTxOKey) where
serialiseToRawBytes :: Hash GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisUTxOKey)
-> ByteString -> Maybe (Hash GenesisUTxOKey)
deserialiseFromRawBytes (AsHash AsGenesisUTxOKey) ByteString
bs =
KeyHash 'Payment StandardCrypto -> Hash GenesisUTxOKey
GenesisUTxOKeyHash (KeyHash 'Payment StandardCrypto -> Hash GenesisUTxOKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisUTxOKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisUTxOKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisUTxOKey) where
textEnvelopeType :: AsType (VerificationKey GenesisUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisUTxOKey)
_ = TextEnvelopeType
"GenesisUTxOVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisUTxOKey) where
textEnvelopeType :: AsType (SigningKey GenesisUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisUTxOKey)
_ = TextEnvelopeType
"GenesisUTxOSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole GenesisUTxOKey PaymentKey where
castVerificationKey :: VerificationKey GenesisUTxOKey -> VerificationKey PaymentKey
castVerificationKey (GenesisUTxOVerificationKey (Sophie.VKey vkey)) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole GenesisUTxOKey PaymentKey where
castSigningKey :: SigningKey GenesisUTxOKey -> SigningKey PaymentKey
castSigningKey (GenesisUTxOSigningKey skey) =
SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
PaymentSigningKey SignKeyDSIGN StandardCrypto
skey
data VestedUTxOKey
instance HasTypeProxy VestedUTxOKey where
data AsType VestedUTxOKey = AsVestedUTxOKey
proxyToAsType :: Proxy VestedUTxOKey -> AsType VestedUTxOKey
proxyToAsType Proxy VestedUTxOKey
_ = AsType VestedUTxOKey
AsVestedUTxOKey
instance Key VestedUTxOKey where
newtype VerificationKey VestedUTxOKey =
VestedUTxOVerificationKey (Sophie.VKey Sophie.Payment StandardCrypto)
deriving stock (VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool
(VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool)
-> (VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool)
-> Eq (VerificationKey VestedUTxOKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool
$c/= :: VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool
== :: VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool
$c== :: VerificationKey VestedUTxOKey
-> VerificationKey VestedUTxOKey -> Bool
Eq)
deriving (Int -> VerificationKey VestedUTxOKey -> ShowS
[VerificationKey VestedUTxOKey] -> ShowS
VerificationKey VestedUTxOKey -> String
(Int -> VerificationKey VestedUTxOKey -> ShowS)
-> (VerificationKey VestedUTxOKey -> String)
-> ([VerificationKey VestedUTxOKey] -> ShowS)
-> Show (VerificationKey VestedUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey VestedUTxOKey] -> ShowS
$cshowList :: [VerificationKey VestedUTxOKey] -> ShowS
show :: VerificationKey VestedUTxOKey -> String
$cshow :: VerificationKey VestedUTxOKey -> String
showsPrec :: Int -> VerificationKey VestedUTxOKey -> ShowS
$cshowsPrec :: Int -> VerificationKey VestedUTxOKey -> ShowS
Show, String -> VerificationKey VestedUTxOKey
(String -> VerificationKey VestedUTxOKey)
-> IsString (VerificationKey VestedUTxOKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey VestedUTxOKey
$cfromString :: String -> VerificationKey VestedUTxOKey
IsString) via UsingRawBytesHex (VerificationKey VestedUTxOKey)
deriving newtype (Typeable (VerificationKey VestedUTxOKey)
Typeable (VerificationKey VestedUTxOKey)
-> (VerificationKey VestedUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedUTxOKey] -> Size)
-> ToCBOR (VerificationKey VestedUTxOKey)
VerificationKey VestedUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedUTxOKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedUTxOKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedUTxOKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedUTxOKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedUTxOKey) -> Size
toCBOR :: VerificationKey VestedUTxOKey -> Encoding
$ctoCBOR :: VerificationKey VestedUTxOKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey VestedUTxOKey)
ToCBOR, Typeable (VerificationKey VestedUTxOKey)
Decoder s (VerificationKey VestedUTxOKey)
Typeable (VerificationKey VestedUTxOKey)
-> (forall s. Decoder s (VerificationKey VestedUTxOKey))
-> (Proxy (VerificationKey VestedUTxOKey) -> Text)
-> FromCBOR (VerificationKey VestedUTxOKey)
Proxy (VerificationKey VestedUTxOKey) -> Text
forall s. Decoder s (VerificationKey VestedUTxOKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey VestedUTxOKey) -> Text
$clabel :: Proxy (VerificationKey VestedUTxOKey) -> Text
fromCBOR :: Decoder s (VerificationKey VestedUTxOKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey VestedUTxOKey)
$cp1FromCBOR :: Typeable (VerificationKey VestedUTxOKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey VestedUTxOKey)
HasTypeProxy (VerificationKey VestedUTxOKey)
-> (VerificationKey VestedUTxOKey -> ByteString)
-> (AsType (VerificationKey VestedUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedUTxOKey))
-> SerialiseAsCBOR (VerificationKey VestedUTxOKey)
AsType (VerificationKey VestedUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedUTxOKey)
VerificationKey VestedUTxOKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey VestedUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedUTxOKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey VestedUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedUTxOKey)
serialiseToCBOR :: VerificationKey VestedUTxOKey -> ByteString
$cserialiseToCBOR :: VerificationKey VestedUTxOKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey VestedUTxOKey)
SerialiseAsCBOR
newtype SigningKey VestedUTxOKey =
VestedUTxOSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey VestedUTxOKey -> ShowS
[SigningKey VestedUTxOKey] -> ShowS
SigningKey VestedUTxOKey -> String
(Int -> SigningKey VestedUTxOKey -> ShowS)
-> (SigningKey VestedUTxOKey -> String)
-> ([SigningKey VestedUTxOKey] -> ShowS)
-> Show (SigningKey VestedUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey VestedUTxOKey] -> ShowS
$cshowList :: [SigningKey VestedUTxOKey] -> ShowS
show :: SigningKey VestedUTxOKey -> String
$cshow :: SigningKey VestedUTxOKey -> String
showsPrec :: Int -> SigningKey VestedUTxOKey -> ShowS
$cshowsPrec :: Int -> SigningKey VestedUTxOKey -> ShowS
Show, String -> SigningKey VestedUTxOKey
(String -> SigningKey VestedUTxOKey)
-> IsString (SigningKey VestedUTxOKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey VestedUTxOKey
$cfromString :: String -> SigningKey VestedUTxOKey
IsString) via UsingRawBytesHex (SigningKey VestedUTxOKey)
deriving newtype (Typeable (SigningKey VestedUTxOKey)
Typeable (SigningKey VestedUTxOKey)
-> (SigningKey VestedUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedUTxOKey] -> Size)
-> ToCBOR (SigningKey VestedUTxOKey)
SigningKey VestedUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedUTxOKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedUTxOKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedUTxOKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedUTxOKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedUTxOKey) -> Size
toCBOR :: SigningKey VestedUTxOKey -> Encoding
$ctoCBOR :: SigningKey VestedUTxOKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey VestedUTxOKey)
ToCBOR, Typeable (SigningKey VestedUTxOKey)
Decoder s (SigningKey VestedUTxOKey)
Typeable (SigningKey VestedUTxOKey)
-> (forall s. Decoder s (SigningKey VestedUTxOKey))
-> (Proxy (SigningKey VestedUTxOKey) -> Text)
-> FromCBOR (SigningKey VestedUTxOKey)
Proxy (SigningKey VestedUTxOKey) -> Text
forall s. Decoder s (SigningKey VestedUTxOKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey VestedUTxOKey) -> Text
$clabel :: Proxy (SigningKey VestedUTxOKey) -> Text
fromCBOR :: Decoder s (SigningKey VestedUTxOKey)
$cfromCBOR :: forall s. Decoder s (SigningKey VestedUTxOKey)
$cp1FromCBOR :: Typeable (SigningKey VestedUTxOKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey VestedUTxOKey)
HasTypeProxy (SigningKey VestedUTxOKey)
-> (SigningKey VestedUTxOKey -> ByteString)
-> (AsType (SigningKey VestedUTxOKey)
-> ByteString -> Either DecoderError (SigningKey VestedUTxOKey))
-> SerialiseAsCBOR (SigningKey VestedUTxOKey)
AsType (SigningKey VestedUTxOKey)
-> ByteString -> Either DecoderError (SigningKey VestedUTxOKey)
SigningKey VestedUTxOKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey VestedUTxOKey)
-> ByteString -> Either DecoderError (SigningKey VestedUTxOKey)
$cdeserialiseFromCBOR :: AsType (SigningKey VestedUTxOKey)
-> ByteString -> Either DecoderError (SigningKey VestedUTxOKey)
serialiseToCBOR :: SigningKey VestedUTxOKey -> ByteString
$cserialiseToCBOR :: SigningKey VestedUTxOKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey VestedUTxOKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType VestedUTxOKey -> Crypto.Seed -> SigningKey VestedUTxOKey
deterministicSigningKey :: AsType VestedUTxOKey -> Seed -> SigningKey VestedUTxOKey
deterministicSigningKey AsType VestedUTxOKey
AsVestedUTxOKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey VestedUTxOKey
VestedUTxOSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType VestedUTxOKey -> Word
deterministicSigningKeySeedSize :: AsType VestedUTxOKey -> Word
deterministicSigningKeySeedSize AsType VestedUTxOKey
AsVestedUTxOKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey VestedUTxOKey -> VerificationKey VestedUTxOKey
getVerificationKey :: SigningKey VestedUTxOKey -> VerificationKey VestedUTxOKey
getVerificationKey (VestedUTxOSigningKey sk) =
VKey 'Payment StandardCrypto -> VerificationKey VestedUTxOKey
VestedUTxOVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey VestedUTxOKey -> Hash VestedUTxOKey
verificationKeyHash :: VerificationKey VestedUTxOKey -> Hash VestedUTxOKey
verificationKeyHash (VestedUTxOVerificationKey vkey) =
KeyHash 'Payment StandardCrypto -> Hash VestedUTxOKey
VestedUTxOKeyHash (VKey 'Payment StandardCrypto -> KeyHash 'Payment StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Payment StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey VestedUTxOKey) where
serialiseToRawBytes :: VerificationKey VestedUTxOKey -> ByteString
serialiseToRawBytes (VestedUTxOVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey VestedUTxOKey)
-> ByteString -> Maybe (VerificationKey VestedUTxOKey)
deserialiseFromRawBytes (AsVerificationKey AsVestedUTxOKey) ByteString
bs =
VKey 'Payment StandardCrypto -> VerificationKey VestedUTxOKey
VestedUTxOVerificationKey (VKey 'Payment StandardCrypto -> VerificationKey VestedUTxOKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey VestedUTxOKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey VestedUTxOKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey VestedUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey VestedUTxOKey) where
serialiseToRawBytes :: SigningKey VestedUTxOKey -> ByteString
serialiseToRawBytes (VestedUTxOSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey VestedUTxOKey)
-> ByteString -> Maybe (SigningKey VestedUTxOKey)
deserialiseFromRawBytes (AsSigningKey AsVestedUTxOKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey VestedUTxOKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey VestedUTxOKey
VestedUTxOSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey VestedUTxOKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey VestedUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash VestedUTxOKey =
VestedUTxOKeyHash (Sophie.KeyHash Sophie.Payment StandardCrypto)
deriving stock (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
(Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool)
-> Eq (Hash VestedUTxOKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
$c/= :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
== :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
$c== :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
Eq, Eq (Hash VestedUTxOKey)
Eq (Hash VestedUTxOKey)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Ordering)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey)
-> (Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey)
-> Ord (Hash VestedUTxOKey)
Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
Hash VestedUTxOKey -> Hash VestedUTxOKey -> Ordering
Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey
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
min :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey
$cmin :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey
max :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey
$cmax :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Hash VestedUTxOKey
>= :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
$c>= :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
> :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
$c> :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
<= :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
$c<= :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
< :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
$c< :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Bool
compare :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Ordering
$ccompare :: Hash VestedUTxOKey -> Hash VestedUTxOKey -> Ordering
$cp1Ord :: Eq (Hash VestedUTxOKey)
Ord)
deriving (Int -> Hash VestedUTxOKey -> ShowS
[Hash VestedUTxOKey] -> ShowS
Hash VestedUTxOKey -> String
(Int -> Hash VestedUTxOKey -> ShowS)
-> (Hash VestedUTxOKey -> String)
-> ([Hash VestedUTxOKey] -> ShowS)
-> Show (Hash VestedUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash VestedUTxOKey] -> ShowS
$cshowList :: [Hash VestedUTxOKey] -> ShowS
show :: Hash VestedUTxOKey -> String
$cshow :: Hash VestedUTxOKey -> String
showsPrec :: Int -> Hash VestedUTxOKey -> ShowS
$cshowsPrec :: Int -> Hash VestedUTxOKey -> ShowS
Show, String -> Hash VestedUTxOKey
(String -> Hash VestedUTxOKey) -> IsString (Hash VestedUTxOKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash VestedUTxOKey
$cfromString :: String -> Hash VestedUTxOKey
IsString) via UsingRawBytesHex (Hash VestedUTxOKey)
deriving (Typeable (Hash VestedUTxOKey)
Typeable (Hash VestedUTxOKey)
-> (Hash VestedUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedUTxOKey] -> Size)
-> ToCBOR (Hash VestedUTxOKey)
Hash VestedUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedUTxOKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedUTxOKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedUTxOKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedUTxOKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedUTxOKey) -> Size
toCBOR :: Hash VestedUTxOKey -> Encoding
$ctoCBOR :: Hash VestedUTxOKey -> Encoding
$cp1ToCBOR :: Typeable (Hash VestedUTxOKey)
ToCBOR, Typeable (Hash VestedUTxOKey)
Decoder s (Hash VestedUTxOKey)
Typeable (Hash VestedUTxOKey)
-> (forall s. Decoder s (Hash VestedUTxOKey))
-> (Proxy (Hash VestedUTxOKey) -> Text)
-> FromCBOR (Hash VestedUTxOKey)
Proxy (Hash VestedUTxOKey) -> Text
forall s. Decoder s (Hash VestedUTxOKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash VestedUTxOKey) -> Text
$clabel :: Proxy (Hash VestedUTxOKey) -> Text
fromCBOR :: Decoder s (Hash VestedUTxOKey)
$cfromCBOR :: forall s. Decoder s (Hash VestedUTxOKey)
$cp1FromCBOR :: Typeable (Hash VestedUTxOKey)
FromCBOR) via UsingRawBytes (Hash VestedUTxOKey)
deriving anyclass HasTypeProxy (Hash VestedUTxOKey)
HasTypeProxy (Hash VestedUTxOKey)
-> (Hash VestedUTxOKey -> ByteString)
-> (AsType (Hash VestedUTxOKey)
-> ByteString -> Either DecoderError (Hash VestedUTxOKey))
-> SerialiseAsCBOR (Hash VestedUTxOKey)
AsType (Hash VestedUTxOKey)
-> ByteString -> Either DecoderError (Hash VestedUTxOKey)
Hash VestedUTxOKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash VestedUTxOKey)
-> ByteString -> Either DecoderError (Hash VestedUTxOKey)
$cdeserialiseFromCBOR :: AsType (Hash VestedUTxOKey)
-> ByteString -> Either DecoderError (Hash VestedUTxOKey)
serialiseToCBOR :: Hash VestedUTxOKey -> ByteString
$cserialiseToCBOR :: Hash VestedUTxOKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash VestedUTxOKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash VestedUTxOKey) where
serialiseToRawBytes :: Hash VestedUTxOKey -> ByteString
serialiseToRawBytes (VestedUTxOKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash VestedUTxOKey)
-> ByteString -> Maybe (Hash VestedUTxOKey)
deserialiseFromRawBytes (AsHash AsVestedUTxOKey) ByteString
bs =
KeyHash 'Payment StandardCrypto -> Hash VestedUTxOKey
VestedUTxOKeyHash (KeyHash 'Payment StandardCrypto -> Hash VestedUTxOKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedUTxOKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Payment StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> Hash VestedUTxOKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash VestedUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey VestedUTxOKey) where
textEnvelopeType :: AsType (VerificationKey VestedUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey VestedUTxOKey)
_ = TextEnvelopeType
"VestedUTxOVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey VestedUTxOKey) where
textEnvelopeType :: AsType (SigningKey VestedUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey VestedUTxOKey)
_ = TextEnvelopeType
"VestedUTxOSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole VestedUTxOKey PaymentKey where
castVerificationKey :: VerificationKey VestedUTxOKey -> VerificationKey PaymentKey
castVerificationKey (VestedUTxOVerificationKey (Sophie.VKey vkey)) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Payment StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole VestedUTxOKey PaymentKey where
castSigningKey :: SigningKey VestedUTxOKey -> SigningKey PaymentKey
castSigningKey (VestedUTxOSigningKey skey) =
SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
PaymentSigningKey SignKeyDSIGN StandardCrypto
skey
data GenesisVestedKey
instance HasTypeProxy GenesisVestedKey where
data AsType GenesisVestedKey = AsGenesisVestedKey
proxyToAsType :: Proxy GenesisVestedKey -> AsType GenesisVestedKey
proxyToAsType Proxy GenesisVestedKey
_ = AsType GenesisVestedKey
AsGenesisVestedKey
instance Key GenesisVestedKey where
newtype VerificationKey GenesisVestedKey =
GenesisVestedVerificationKey (Sophie.VKey Sophie.Genesis StandardCrypto)
deriving stock (VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool
(VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool)
-> (VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool)
-> Eq (VerificationKey GenesisVestedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool
$c/= :: VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool
== :: VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool
$c== :: VerificationKey GenesisVestedKey
-> VerificationKey GenesisVestedKey -> Bool
Eq)
deriving (Int -> VerificationKey GenesisVestedKey -> ShowS
[VerificationKey GenesisVestedKey] -> ShowS
VerificationKey GenesisVestedKey -> String
(Int -> VerificationKey GenesisVestedKey -> ShowS)
-> (VerificationKey GenesisVestedKey -> String)
-> ([VerificationKey GenesisVestedKey] -> ShowS)
-> Show (VerificationKey GenesisVestedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisVestedKey] -> ShowS
$cshowList :: [VerificationKey GenesisVestedKey] -> ShowS
show :: VerificationKey GenesisVestedKey -> String
$cshow :: VerificationKey GenesisVestedKey -> String
showsPrec :: Int -> VerificationKey GenesisVestedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisVestedKey -> ShowS
Show, String -> VerificationKey GenesisVestedKey
(String -> VerificationKey GenesisVestedKey)
-> IsString (VerificationKey GenesisVestedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisVestedKey
$cfromString :: String -> VerificationKey GenesisVestedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisVestedKey)
deriving newtype (Typeable (VerificationKey GenesisVestedKey)
Typeable (VerificationKey GenesisVestedKey)
-> (VerificationKey GenesisVestedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedKey] -> Size)
-> ToCBOR (VerificationKey GenesisVestedKey)
VerificationKey GenesisVestedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedKey) -> Size
toCBOR :: VerificationKey GenesisVestedKey -> Encoding
$ctoCBOR :: VerificationKey GenesisVestedKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey GenesisVestedKey)
ToCBOR, Typeable (VerificationKey GenesisVestedKey)
Decoder s (VerificationKey GenesisVestedKey)
Typeable (VerificationKey GenesisVestedKey)
-> (forall s. Decoder s (VerificationKey GenesisVestedKey))
-> (Proxy (VerificationKey GenesisVestedKey) -> Text)
-> FromCBOR (VerificationKey GenesisVestedKey)
Proxy (VerificationKey GenesisVestedKey) -> Text
forall s. Decoder s (VerificationKey GenesisVestedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey GenesisVestedKey) -> Text
$clabel :: Proxy (VerificationKey GenesisVestedKey) -> Text
fromCBOR :: Decoder s (VerificationKey GenesisVestedKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisVestedKey)
$cp1FromCBOR :: Typeable (VerificationKey GenesisVestedKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey GenesisVestedKey)
HasTypeProxy (VerificationKey GenesisVestedKey)
-> (VerificationKey GenesisVestedKey -> ByteString)
-> (AsType (VerificationKey GenesisVestedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedKey))
-> SerialiseAsCBOR (VerificationKey GenesisVestedKey)
AsType (VerificationKey GenesisVestedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedKey)
VerificationKey GenesisVestedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisVestedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisVestedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedKey)
serialiseToCBOR :: VerificationKey GenesisVestedKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisVestedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisVestedKey)
SerialiseAsCBOR
newtype SigningKey GenesisVestedKey =
GenesisVestedSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisVestedKey -> ShowS
[SigningKey GenesisVestedKey] -> ShowS
SigningKey GenesisVestedKey -> String
(Int -> SigningKey GenesisVestedKey -> ShowS)
-> (SigningKey GenesisVestedKey -> String)
-> ([SigningKey GenesisVestedKey] -> ShowS)
-> Show (SigningKey GenesisVestedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisVestedKey] -> ShowS
$cshowList :: [SigningKey GenesisVestedKey] -> ShowS
show :: SigningKey GenesisVestedKey -> String
$cshow :: SigningKey GenesisVestedKey -> String
showsPrec :: Int -> SigningKey GenesisVestedKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisVestedKey -> ShowS
Show, String -> SigningKey GenesisVestedKey
(String -> SigningKey GenesisVestedKey)
-> IsString (SigningKey GenesisVestedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisVestedKey
$cfromString :: String -> SigningKey GenesisVestedKey
IsString) via UsingRawBytesHex (SigningKey GenesisVestedKey)
deriving newtype (Typeable (SigningKey GenesisVestedKey)
Typeable (SigningKey GenesisVestedKey)
-> (SigningKey GenesisVestedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedKey] -> Size)
-> ToCBOR (SigningKey GenesisVestedKey)
SigningKey GenesisVestedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedKey) -> Size
toCBOR :: SigningKey GenesisVestedKey -> Encoding
$ctoCBOR :: SigningKey GenesisVestedKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey GenesisVestedKey)
ToCBOR, Typeable (SigningKey GenesisVestedKey)
Decoder s (SigningKey GenesisVestedKey)
Typeable (SigningKey GenesisVestedKey)
-> (forall s. Decoder s (SigningKey GenesisVestedKey))
-> (Proxy (SigningKey GenesisVestedKey) -> Text)
-> FromCBOR (SigningKey GenesisVestedKey)
Proxy (SigningKey GenesisVestedKey) -> Text
forall s. Decoder s (SigningKey GenesisVestedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey GenesisVestedKey) -> Text
$clabel :: Proxy (SigningKey GenesisVestedKey) -> Text
fromCBOR :: Decoder s (SigningKey GenesisVestedKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisVestedKey)
$cp1FromCBOR :: Typeable (SigningKey GenesisVestedKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey GenesisVestedKey)
HasTypeProxy (SigningKey GenesisVestedKey)
-> (SigningKey GenesisVestedKey -> ByteString)
-> (AsType (SigningKey GenesisVestedKey)
-> ByteString -> Either DecoderError (SigningKey GenesisVestedKey))
-> SerialiseAsCBOR (SigningKey GenesisVestedKey)
AsType (SigningKey GenesisVestedKey)
-> ByteString -> Either DecoderError (SigningKey GenesisVestedKey)
SigningKey GenesisVestedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisVestedKey)
-> ByteString -> Either DecoderError (SigningKey GenesisVestedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisVestedKey)
-> ByteString -> Either DecoderError (SigningKey GenesisVestedKey)
serialiseToCBOR :: SigningKey GenesisVestedKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisVestedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisVestedKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisVestedKey -> Crypto.Seed -> SigningKey GenesisVestedKey
deterministicSigningKey :: AsType GenesisVestedKey -> Seed -> SigningKey GenesisVestedKey
deterministicSigningKey AsType GenesisVestedKey
AsGenesisVestedKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisVestedKey
GenesisVestedSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisVestedKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisVestedKey -> Word
deterministicSigningKeySeedSize AsType GenesisVestedKey
AsGenesisVestedKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisVestedKey -> VerificationKey GenesisVestedKey
getVerificationKey :: SigningKey GenesisVestedKey -> VerificationKey GenesisVestedKey
getVerificationKey (GenesisVestedSigningKey sk) =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisVestedKey
GenesisVestedVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Genesis StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey GenesisVestedKey -> Hash GenesisVestedKey
verificationKeyHash :: VerificationKey GenesisVestedKey -> Hash GenesisVestedKey
verificationKeyHash (GenesisVestedVerificationKey vkey) =
KeyHash 'Genesis StandardCrypto -> Hash GenesisVestedKey
GenesisVestedKeyHash (VKey 'Genesis StandardCrypto -> KeyHash 'Genesis StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Genesis StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisVestedKey) where
serialiseToRawBytes :: VerificationKey GenesisVestedKey -> ByteString
serialiseToRawBytes (GenesisVestedVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisVestedKey)
-> ByteString -> Maybe (VerificationKey GenesisVestedKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisVestedKey) ByteString
bs =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisVestedKey
GenesisVestedVerificationKey (VKey 'Genesis StandardCrypto -> VerificationKey GenesisVestedKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey GenesisVestedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey GenesisVestedKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey GenesisVestedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisVestedKey) where
serialiseToRawBytes :: SigningKey GenesisVestedKey -> ByteString
serialiseToRawBytes (GenesisVestedSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisVestedKey)
-> ByteString -> Maybe (SigningKey GenesisVestedKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisVestedKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisVestedKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisVestedKey
GenesisVestedSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisVestedKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey GenesisVestedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisVestedKey =
GenesisVestedKeyHash (Sophie.KeyHash Sophie.Genesis StandardCrypto)
deriving stock (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
(Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool)
-> (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool)
-> Eq (Hash GenesisVestedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
$c/= :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
== :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
$c== :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
Eq, Eq (Hash GenesisVestedKey)
Eq (Hash GenesisVestedKey)
-> (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Ordering)
-> (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool)
-> (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool)
-> (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool)
-> (Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool)
-> (Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey)
-> (Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey)
-> Ord (Hash GenesisVestedKey)
Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
Hash GenesisVestedKey -> Hash GenesisVestedKey -> Ordering
Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey
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
min :: Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey
$cmin :: Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey
max :: Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey
$cmax :: Hash GenesisVestedKey
-> Hash GenesisVestedKey -> Hash GenesisVestedKey
>= :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
$c>= :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
> :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
$c> :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
<= :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
$c<= :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
< :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
$c< :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Bool
compare :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Ordering
$ccompare :: Hash GenesisVestedKey -> Hash GenesisVestedKey -> Ordering
$cp1Ord :: Eq (Hash GenesisVestedKey)
Ord)
deriving (Int -> Hash GenesisVestedKey -> ShowS
[Hash GenesisVestedKey] -> ShowS
Hash GenesisVestedKey -> String
(Int -> Hash GenesisVestedKey -> ShowS)
-> (Hash GenesisVestedKey -> String)
-> ([Hash GenesisVestedKey] -> ShowS)
-> Show (Hash GenesisVestedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisVestedKey] -> ShowS
$cshowList :: [Hash GenesisVestedKey] -> ShowS
show :: Hash GenesisVestedKey -> String
$cshow :: Hash GenesisVestedKey -> String
showsPrec :: Int -> Hash GenesisVestedKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisVestedKey -> ShowS
Show, String -> Hash GenesisVestedKey
(String -> Hash GenesisVestedKey)
-> IsString (Hash GenesisVestedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisVestedKey
$cfromString :: String -> Hash GenesisVestedKey
IsString) via UsingRawBytesHex (Hash GenesisVestedKey)
deriving (Typeable (Hash GenesisVestedKey)
Typeable (Hash GenesisVestedKey)
-> (Hash GenesisVestedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedKey] -> Size)
-> ToCBOR (Hash GenesisVestedKey)
Hash GenesisVestedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedKey) -> Size
toCBOR :: Hash GenesisVestedKey -> Encoding
$ctoCBOR :: Hash GenesisVestedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisVestedKey)
ToCBOR, Typeable (Hash GenesisVestedKey)
Decoder s (Hash GenesisVestedKey)
Typeable (Hash GenesisVestedKey)
-> (forall s. Decoder s (Hash GenesisVestedKey))
-> (Proxy (Hash GenesisVestedKey) -> Text)
-> FromCBOR (Hash GenesisVestedKey)
Proxy (Hash GenesisVestedKey) -> Text
forall s. Decoder s (Hash GenesisVestedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisVestedKey) -> Text
$clabel :: Proxy (Hash GenesisVestedKey) -> Text
fromCBOR :: Decoder s (Hash GenesisVestedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisVestedKey)
$cp1FromCBOR :: Typeable (Hash GenesisVestedKey)
FromCBOR) via UsingRawBytes (Hash GenesisVestedKey)
deriving anyclass HasTypeProxy (Hash GenesisVestedKey)
HasTypeProxy (Hash GenesisVestedKey)
-> (Hash GenesisVestedKey -> ByteString)
-> (AsType (Hash GenesisVestedKey)
-> ByteString -> Either DecoderError (Hash GenesisVestedKey))
-> SerialiseAsCBOR (Hash GenesisVestedKey)
AsType (Hash GenesisVestedKey)
-> ByteString -> Either DecoderError (Hash GenesisVestedKey)
Hash GenesisVestedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisVestedKey)
-> ByteString -> Either DecoderError (Hash GenesisVestedKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisVestedKey)
-> ByteString -> Either DecoderError (Hash GenesisVestedKey)
serialiseToCBOR :: Hash GenesisVestedKey -> ByteString
$cserialiseToCBOR :: Hash GenesisVestedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisVestedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisVestedKey) where
serialiseToRawBytes :: Hash GenesisVestedKey -> ByteString
serialiseToRawBytes (GenesisVestedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisVestedKey)
-> ByteString -> Maybe (Hash GenesisVestedKey)
deserialiseFromRawBytes (AsHash AsGenesisVestedKey) ByteString
bs =
KeyHash 'Genesis StandardCrypto -> Hash GenesisVestedKey
GenesisVestedKeyHash (KeyHash 'Genesis StandardCrypto -> Hash GenesisVestedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Genesis StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Genesis StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisVestedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisVestedKey) where
textEnvelopeType :: AsType (VerificationKey GenesisVestedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisVestedKey)
_ = TextEnvelopeType
"GenesisVestedVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisVestedKey) where
textEnvelopeType :: AsType (SigningKey GenesisVestedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisVestedKey)
_ = TextEnvelopeType
"GenesisVestedSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
data GenesisVestedExtendedKey
instance HasTypeProxy GenesisVestedExtendedKey where
data AsType GenesisVestedExtendedKey = AsGenesisVestedExtendedKey
proxyToAsType :: Proxy GenesisVestedExtendedKey -> AsType GenesisVestedExtendedKey
proxyToAsType Proxy GenesisVestedExtendedKey
_ = AsType GenesisVestedExtendedKey
AsGenesisVestedExtendedKey
instance Key GenesisVestedExtendedKey where
newtype VerificationKey GenesisVestedExtendedKey =
GenesisVestedExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool
(VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool)
-> (VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool)
-> Eq (VerificationKey GenesisVestedExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool
$c/= :: VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool
== :: VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool
$c== :: VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey GenesisVestedExtendedKey)
HasTypeProxy (VerificationKey GenesisVestedExtendedKey)
-> (VerificationKey GenesisVestedExtendedKey -> ByteString)
-> (AsType (VerificationKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedExtendedKey))
-> SerialiseAsCBOR (VerificationKey GenesisVestedExtendedKey)
AsType (VerificationKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedExtendedKey)
VerificationKey GenesisVestedExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedExtendedKey)
serialiseToCBOR :: VerificationKey GenesisVestedExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisVestedExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisVestedExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey GenesisVestedExtendedKey -> ShowS
[VerificationKey GenesisVestedExtendedKey] -> ShowS
VerificationKey GenesisVestedExtendedKey -> String
(Int -> VerificationKey GenesisVestedExtendedKey -> ShowS)
-> (VerificationKey GenesisVestedExtendedKey -> String)
-> ([VerificationKey GenesisVestedExtendedKey] -> ShowS)
-> Show (VerificationKey GenesisVestedExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisVestedExtendedKey] -> ShowS
$cshowList :: [VerificationKey GenesisVestedExtendedKey] -> ShowS
show :: VerificationKey GenesisVestedExtendedKey -> String
$cshow :: VerificationKey GenesisVestedExtendedKey -> String
showsPrec :: Int -> VerificationKey GenesisVestedExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisVestedExtendedKey -> ShowS
Show, String -> VerificationKey GenesisVestedExtendedKey
(String -> VerificationKey GenesisVestedExtendedKey)
-> IsString (VerificationKey GenesisVestedExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisVestedExtendedKey
$cfromString :: String -> VerificationKey GenesisVestedExtendedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisVestedExtendedKey)
newtype SigningKey GenesisVestedExtendedKey =
GenesisVestedExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey GenesisVestedExtendedKey)
HasTypeProxy (SigningKey GenesisVestedExtendedKey)
-> (SigningKey GenesisVestedExtendedKey -> ByteString)
-> (AsType (SigningKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedExtendedKey))
-> SerialiseAsCBOR (SigningKey GenesisVestedExtendedKey)
AsType (SigningKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedExtendedKey)
SigningKey GenesisVestedExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedExtendedKey)
serialiseToCBOR :: SigningKey GenesisVestedExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisVestedExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisVestedExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey GenesisVestedExtendedKey -> ShowS
[SigningKey GenesisVestedExtendedKey] -> ShowS
SigningKey GenesisVestedExtendedKey -> String
(Int -> SigningKey GenesisVestedExtendedKey -> ShowS)
-> (SigningKey GenesisVestedExtendedKey -> String)
-> ([SigningKey GenesisVestedExtendedKey] -> ShowS)
-> Show (SigningKey GenesisVestedExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisVestedExtendedKey] -> ShowS
$cshowList :: [SigningKey GenesisVestedExtendedKey] -> ShowS
show :: SigningKey GenesisVestedExtendedKey -> String
$cshow :: SigningKey GenesisVestedExtendedKey -> String
showsPrec :: Int -> SigningKey GenesisVestedExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisVestedExtendedKey -> ShowS
Show, String -> SigningKey GenesisVestedExtendedKey
(String -> SigningKey GenesisVestedExtendedKey)
-> IsString (SigningKey GenesisVestedExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisVestedExtendedKey
$cfromString :: String -> SigningKey GenesisVestedExtendedKey
IsString) via UsingRawBytesHex (SigningKey GenesisVestedExtendedKey)
deterministicSigningKey :: AsType GenesisVestedExtendedKey
-> Crypto.Seed
-> SigningKey GenesisVestedExtendedKey
deterministicSigningKey :: AsType GenesisVestedExtendedKey
-> Seed -> SigningKey GenesisVestedExtendedKey
deterministicSigningKey AsType GenesisVestedExtendedKey
AsGenesisVestedExtendedKey Seed
seed =
XPrv -> SigningKey GenesisVestedExtendedKey
GenesisVestedExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType GenesisVestedExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisVestedExtendedKey -> Word
deterministicSigningKeySeedSize AsType GenesisVestedExtendedKey
AsGenesisVestedExtendedKey = Word
32
getVerificationKey :: SigningKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey
getVerificationKey :: SigningKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedExtendedKey
getVerificationKey (GenesisVestedExtendedSigningKey sk) =
XPub -> VerificationKey GenesisVestedExtendedKey
GenesisVestedExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey
verificationKeyHash :: VerificationKey GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey
verificationKeyHash (GenesisVestedExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto -> Hash GenesisVestedExtendedKey
GenesisVestedExtendedKeyHash
(KeyHash 'Staking StandardCrypto -> Hash GenesisVestedExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash GenesisVestedExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash GenesisVestedExtendedKey)
-> Hash Blake2b_224 XPub -> Hash GenesisVestedExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey GenesisVestedExtendedKey) where
toCBOR :: VerificationKey GenesisVestedExtendedKey -> Encoding
toCBOR (GenesisVestedExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey GenesisVestedExtendedKey) where
fromCBOR :: Decoder s (VerificationKey GenesisVestedExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey GenesisVestedExtendedKey))
-> (XPub -> Decoder s (VerificationKey GenesisVestedExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey GenesisVestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey GenesisVestedExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey GenesisVestedExtendedKey
-> Decoder s (VerificationKey GenesisVestedExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey GenesisVestedExtendedKey
-> Decoder s (VerificationKey GenesisVestedExtendedKey))
-> (XPub -> VerificationKey GenesisVestedExtendedKey)
-> XPub
-> Decoder s (VerificationKey GenesisVestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisVestedExtendedKey
GenesisVestedExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey GenesisVestedExtendedKey) where
toCBOR :: SigningKey GenesisVestedExtendedKey -> Encoding
toCBOR (GenesisVestedExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey GenesisVestedExtendedKey) where
fromCBOR :: Decoder s (SigningKey GenesisVestedExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey GenesisVestedExtendedKey))
-> (XPrv -> Decoder s (SigningKey GenesisVestedExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey GenesisVestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey GenesisVestedExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey GenesisVestedExtendedKey
-> Decoder s (SigningKey GenesisVestedExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey GenesisVestedExtendedKey
-> Decoder s (SigningKey GenesisVestedExtendedKey))
-> (XPrv -> SigningKey GenesisVestedExtendedKey)
-> XPrv
-> Decoder s (SigningKey GenesisVestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisVestedExtendedKey
GenesisVestedExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey GenesisVestedExtendedKey) where
serialiseToRawBytes :: VerificationKey GenesisVestedExtendedKey -> ByteString
serialiseToRawBytes (GenesisVestedExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey GenesisVestedExtendedKey)
-> ByteString -> Maybe (VerificationKey GenesisVestedExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisVestedExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey GenesisVestedExtendedKey))
-> (XPub -> Maybe (VerificationKey GenesisVestedExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey GenesisVestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey GenesisVestedExtendedKey)
-> String -> Maybe (VerificationKey GenesisVestedExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey GenesisVestedExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey GenesisVestedExtendedKey
-> Maybe (VerificationKey GenesisVestedExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey GenesisVestedExtendedKey
-> Maybe (VerificationKey GenesisVestedExtendedKey))
-> (XPub -> VerificationKey GenesisVestedExtendedKey)
-> XPub
-> Maybe (VerificationKey GenesisVestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisVestedExtendedKey
GenesisVestedExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey GenesisVestedExtendedKey) where
serialiseToRawBytes :: SigningKey GenesisVestedExtendedKey -> ByteString
serialiseToRawBytes (GenesisVestedExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey GenesisVestedExtendedKey)
-> ByteString -> Maybe (SigningKey GenesisVestedExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisVestedExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey GenesisVestedExtendedKey))
-> (XPrv -> Maybe (SigningKey GenesisVestedExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey GenesisVestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey GenesisVestedExtendedKey)
-> String -> Maybe (SigningKey GenesisVestedExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey GenesisVestedExtendedKey)
forall a. Maybe a
Nothing) (SigningKey GenesisVestedExtendedKey
-> Maybe (SigningKey GenesisVestedExtendedKey)
forall a. a -> Maybe a
Just (SigningKey GenesisVestedExtendedKey
-> Maybe (SigningKey GenesisVestedExtendedKey))
-> (XPrv -> SigningKey GenesisVestedExtendedKey)
-> XPrv
-> Maybe (SigningKey GenesisVestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisVestedExtendedKey
GenesisVestedExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
newtype instance Hash GenesisVestedExtendedKey =
GenesisVestedExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
(Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool)
-> Eq (Hash GenesisVestedExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
$c/= :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
== :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
$c== :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
Eq, Eq (Hash GenesisVestedExtendedKey)
Eq (Hash GenesisVestedExtendedKey)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Ordering)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey)
-> (Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey)
-> Ord (Hash GenesisVestedExtendedKey)
Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Ordering
Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey
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
min :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey
$cmin :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey
max :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey
$cmax :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Hash GenesisVestedExtendedKey
>= :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
$c>= :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
> :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
$c> :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
<= :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
$c<= :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
< :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
$c< :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Bool
compare :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Ordering
$ccompare :: Hash GenesisVestedExtendedKey
-> Hash GenesisVestedExtendedKey -> Ordering
$cp1Ord :: Eq (Hash GenesisVestedExtendedKey)
Ord)
deriving (Int -> Hash GenesisVestedExtendedKey -> ShowS
[Hash GenesisVestedExtendedKey] -> ShowS
Hash GenesisVestedExtendedKey -> String
(Int -> Hash GenesisVestedExtendedKey -> ShowS)
-> (Hash GenesisVestedExtendedKey -> String)
-> ([Hash GenesisVestedExtendedKey] -> ShowS)
-> Show (Hash GenesisVestedExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisVestedExtendedKey] -> ShowS
$cshowList :: [Hash GenesisVestedExtendedKey] -> ShowS
show :: Hash GenesisVestedExtendedKey -> String
$cshow :: Hash GenesisVestedExtendedKey -> String
showsPrec :: Int -> Hash GenesisVestedExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisVestedExtendedKey -> ShowS
Show, String -> Hash GenesisVestedExtendedKey
(String -> Hash GenesisVestedExtendedKey)
-> IsString (Hash GenesisVestedExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisVestedExtendedKey
$cfromString :: String -> Hash GenesisVestedExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisVestedExtendedKey)
deriving (Typeable (Hash GenesisVestedExtendedKey)
Typeable (Hash GenesisVestedExtendedKey)
-> (Hash GenesisVestedExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedExtendedKey] -> Size)
-> ToCBOR (Hash GenesisVestedExtendedKey)
Hash GenesisVestedExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedExtendedKey) -> Size
toCBOR :: Hash GenesisVestedExtendedKey -> Encoding
$ctoCBOR :: Hash GenesisVestedExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisVestedExtendedKey)
ToCBOR, Typeable (Hash GenesisVestedExtendedKey)
Decoder s (Hash GenesisVestedExtendedKey)
Typeable (Hash GenesisVestedExtendedKey)
-> (forall s. Decoder s (Hash GenesisVestedExtendedKey))
-> (Proxy (Hash GenesisVestedExtendedKey) -> Text)
-> FromCBOR (Hash GenesisVestedExtendedKey)
Proxy (Hash GenesisVestedExtendedKey) -> Text
forall s. Decoder s (Hash GenesisVestedExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisVestedExtendedKey) -> Text
$clabel :: Proxy (Hash GenesisVestedExtendedKey) -> Text
fromCBOR :: Decoder s (Hash GenesisVestedExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisVestedExtendedKey)
$cp1FromCBOR :: Typeable (Hash GenesisVestedExtendedKey)
FromCBOR) via UsingRawBytes (Hash GenesisVestedExtendedKey)
deriving anyclass HasTypeProxy (Hash GenesisVestedExtendedKey)
HasTypeProxy (Hash GenesisVestedExtendedKey)
-> (Hash GenesisVestedExtendedKey -> ByteString)
-> (AsType (Hash GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedExtendedKey))
-> SerialiseAsCBOR (Hash GenesisVestedExtendedKey)
AsType (Hash GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedExtendedKey)
Hash GenesisVestedExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisVestedExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedExtendedKey)
serialiseToCBOR :: Hash GenesisVestedExtendedKey -> ByteString
$cserialiseToCBOR :: Hash GenesisVestedExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisVestedExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisVestedExtendedKey) where
serialiseToRawBytes :: Hash GenesisVestedExtendedKey -> ByteString
serialiseToRawBytes (GenesisVestedExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisVestedExtendedKey)
-> ByteString -> Maybe (Hash GenesisVestedExtendedKey)
deserialiseFromRawBytes (AsHash AsGenesisVestedExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash GenesisVestedExtendedKey
GenesisVestedExtendedKeyHash (KeyHash 'Staking StandardCrypto -> Hash GenesisVestedExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisVestedExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisVestedExtendedKey) where
textEnvelopeType :: AsType (VerificationKey GenesisVestedExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisVestedExtendedKey)
_ = TextEnvelopeType
"GenesisVestedExtendedVerificationKey_ed25519_bip32"
instance HasTextEnvelope (SigningKey GenesisVestedExtendedKey) where
textEnvelopeType :: AsType (SigningKey GenesisVestedExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisVestedExtendedKey)
_ = TextEnvelopeType
"GenesisVestedExtendedSigningKey_ed25519_bip32"
instance CastVerificationKeyRole GenesisVestedExtendedKey GenesisVestedKey where
castVerificationKey :: VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedKey
castVerificationKey (GenesisVestedExtendedVerificationKey vk) =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisVestedKey
GenesisVestedVerificationKey
(VKey 'Genesis StandardCrypto -> VerificationKey GenesisVestedKey)
-> (XPub -> VKey 'Genesis StandardCrypto)
-> XPub
-> VerificationKey GenesisVestedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'Genesis StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'Genesis StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey GenesisVestedKey)
-> XPub -> VerificationKey GenesisVestedKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data GenesisVestedDelegateKey
instance HasTypeProxy GenesisVestedDelegateKey where
data AsType GenesisVestedDelegateKey = AsGenesisVestedDelegateKey
proxyToAsType :: Proxy GenesisVestedDelegateKey -> AsType GenesisVestedDelegateKey
proxyToAsType Proxy GenesisVestedDelegateKey
_ = AsType GenesisVestedDelegateKey
AsGenesisVestedDelegateKey
instance Key GenesisVestedDelegateKey where
newtype VerificationKey GenesisVestedDelegateKey =
GenesisVestedDelegateVerificationKey (Sophie.VKey Sophie.VestedDelegate StandardCrypto)
deriving stock (VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool
(VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool)
-> (VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool)
-> Eq (VerificationKey GenesisVestedDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool
$c/= :: VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool
== :: VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool
$c== :: VerificationKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey -> Bool
Eq)
deriving (Int -> VerificationKey GenesisVestedDelegateKey -> ShowS
[VerificationKey GenesisVestedDelegateKey] -> ShowS
VerificationKey GenesisVestedDelegateKey -> String
(Int -> VerificationKey GenesisVestedDelegateKey -> ShowS)
-> (VerificationKey GenesisVestedDelegateKey -> String)
-> ([VerificationKey GenesisVestedDelegateKey] -> ShowS)
-> Show (VerificationKey GenesisVestedDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisVestedDelegateKey] -> ShowS
$cshowList :: [VerificationKey GenesisVestedDelegateKey] -> ShowS
show :: VerificationKey GenesisVestedDelegateKey -> String
$cshow :: VerificationKey GenesisVestedDelegateKey -> String
showsPrec :: Int -> VerificationKey GenesisVestedDelegateKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisVestedDelegateKey -> ShowS
Show, String -> VerificationKey GenesisVestedDelegateKey
(String -> VerificationKey GenesisVestedDelegateKey)
-> IsString (VerificationKey GenesisVestedDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisVestedDelegateKey
$cfromString :: String -> VerificationKey GenesisVestedDelegateKey
IsString) via UsingRawBytesHex (VerificationKey GenesisVestedDelegateKey)
deriving newtype (Typeable (VerificationKey GenesisVestedDelegateKey)
Typeable (VerificationKey GenesisVestedDelegateKey)
-> (VerificationKey GenesisVestedDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedDelegateKey] -> Size)
-> ToCBOR (VerificationKey GenesisVestedDelegateKey)
VerificationKey GenesisVestedDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisVestedDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisVestedDelegateKey) -> Size
toCBOR :: VerificationKey GenesisVestedDelegateKey -> Encoding
$ctoCBOR :: VerificationKey GenesisVestedDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey GenesisVestedDelegateKey)
ToCBOR, Typeable (VerificationKey GenesisVestedDelegateKey)
Decoder s (VerificationKey GenesisVestedDelegateKey)
Typeable (VerificationKey GenesisVestedDelegateKey)
-> (forall s. Decoder s (VerificationKey GenesisVestedDelegateKey))
-> (Proxy (VerificationKey GenesisVestedDelegateKey) -> Text)
-> FromCBOR (VerificationKey GenesisVestedDelegateKey)
Proxy (VerificationKey GenesisVestedDelegateKey) -> Text
forall s. Decoder s (VerificationKey GenesisVestedDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey GenesisVestedDelegateKey) -> Text
$clabel :: Proxy (VerificationKey GenesisVestedDelegateKey) -> Text
fromCBOR :: Decoder s (VerificationKey GenesisVestedDelegateKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisVestedDelegateKey)
$cp1FromCBOR :: Typeable (VerificationKey GenesisVestedDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey GenesisVestedDelegateKey)
HasTypeProxy (VerificationKey GenesisVestedDelegateKey)
-> (VerificationKey GenesisVestedDelegateKey -> ByteString)
-> (AsType (VerificationKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedDelegateKey))
-> SerialiseAsCBOR (VerificationKey GenesisVestedDelegateKey)
AsType (VerificationKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedDelegateKey)
VerificationKey GenesisVestedDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedDelegateKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisVestedDelegateKey)
serialiseToCBOR :: VerificationKey GenesisVestedDelegateKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisVestedDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisVestedDelegateKey)
SerialiseAsCBOR
newtype SigningKey GenesisVestedDelegateKey =
GenesisVestedDelegateSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisVestedDelegateKey -> ShowS
[SigningKey GenesisVestedDelegateKey] -> ShowS
SigningKey GenesisVestedDelegateKey -> String
(Int -> SigningKey GenesisVestedDelegateKey -> ShowS)
-> (SigningKey GenesisVestedDelegateKey -> String)
-> ([SigningKey GenesisVestedDelegateKey] -> ShowS)
-> Show (SigningKey GenesisVestedDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisVestedDelegateKey] -> ShowS
$cshowList :: [SigningKey GenesisVestedDelegateKey] -> ShowS
show :: SigningKey GenesisVestedDelegateKey -> String
$cshow :: SigningKey GenesisVestedDelegateKey -> String
showsPrec :: Int -> SigningKey GenesisVestedDelegateKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisVestedDelegateKey -> ShowS
Show, String -> SigningKey GenesisVestedDelegateKey
(String -> SigningKey GenesisVestedDelegateKey)
-> IsString (SigningKey GenesisVestedDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisVestedDelegateKey
$cfromString :: String -> SigningKey GenesisVestedDelegateKey
IsString) via UsingRawBytesHex (SigningKey GenesisVestedDelegateKey)
deriving newtype (Typeable (SigningKey GenesisVestedDelegateKey)
Typeable (SigningKey GenesisVestedDelegateKey)
-> (SigningKey GenesisVestedDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedDelegateKey] -> Size)
-> ToCBOR (SigningKey GenesisVestedDelegateKey)
SigningKey GenesisVestedDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisVestedDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisVestedDelegateKey) -> Size
toCBOR :: SigningKey GenesisVestedDelegateKey -> Encoding
$ctoCBOR :: SigningKey GenesisVestedDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey GenesisVestedDelegateKey)
ToCBOR, Typeable (SigningKey GenesisVestedDelegateKey)
Decoder s (SigningKey GenesisVestedDelegateKey)
Typeable (SigningKey GenesisVestedDelegateKey)
-> (forall s. Decoder s (SigningKey GenesisVestedDelegateKey))
-> (Proxy (SigningKey GenesisVestedDelegateKey) -> Text)
-> FromCBOR (SigningKey GenesisVestedDelegateKey)
Proxy (SigningKey GenesisVestedDelegateKey) -> Text
forall s. Decoder s (SigningKey GenesisVestedDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey GenesisVestedDelegateKey) -> Text
$clabel :: Proxy (SigningKey GenesisVestedDelegateKey) -> Text
fromCBOR :: Decoder s (SigningKey GenesisVestedDelegateKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisVestedDelegateKey)
$cp1FromCBOR :: Typeable (SigningKey GenesisVestedDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey GenesisVestedDelegateKey)
HasTypeProxy (SigningKey GenesisVestedDelegateKey)
-> (SigningKey GenesisVestedDelegateKey -> ByteString)
-> (AsType (SigningKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedDelegateKey))
-> SerialiseAsCBOR (SigningKey GenesisVestedDelegateKey)
AsType (SigningKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedDelegateKey)
SigningKey GenesisVestedDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedDelegateKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisVestedDelegateKey)
serialiseToCBOR :: SigningKey GenesisVestedDelegateKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisVestedDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisVestedDelegateKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisVestedDelegateKey -> Crypto.Seed -> SigningKey GenesisVestedDelegateKey
deterministicSigningKey :: AsType GenesisVestedDelegateKey
-> Seed -> SigningKey GenesisVestedDelegateKey
deterministicSigningKey AsType GenesisVestedDelegateKey
AsGenesisVestedDelegateKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisVestedDelegateKey
GenesisVestedDelegateSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisVestedDelegateKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisVestedDelegateKey -> Word
deterministicSigningKeySeedSize AsType GenesisVestedDelegateKey
AsGenesisVestedDelegateKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisVestedDelegateKey -> VerificationKey GenesisVestedDelegateKey
getVerificationKey :: SigningKey GenesisVestedDelegateKey
-> VerificationKey GenesisVestedDelegateKey
getVerificationKey (GenesisVestedDelegateSigningKey sk) =
VKey 'VestedDelegate StandardCrypto
-> VerificationKey GenesisVestedDelegateKey
GenesisVestedDelegateVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'VestedDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey
verificationKeyHash :: VerificationKey GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey
verificationKeyHash (GenesisVestedDelegateVerificationKey vkey) =
KeyHash 'VestedDelegate StandardCrypto
-> Hash GenesisVestedDelegateKey
GenesisVestedDelegateKeyHash (VKey 'VestedDelegate StandardCrypto
-> KeyHash 'VestedDelegate StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'VestedDelegate StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisVestedDelegateKey) where
serialiseToRawBytes :: VerificationKey GenesisVestedDelegateKey -> ByteString
serialiseToRawBytes (GenesisVestedDelegateVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisVestedDelegateKey)
-> ByteString -> Maybe (VerificationKey GenesisVestedDelegateKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisVestedDelegateKey) ByteString
bs =
VKey 'VestedDelegate StandardCrypto
-> VerificationKey GenesisVestedDelegateKey
GenesisVestedDelegateVerificationKey (VKey 'VestedDelegate StandardCrypto
-> VerificationKey GenesisVestedDelegateKey)
-> (VerKeyDSIGN Ed25519DSIGN
-> VKey 'VestedDelegate StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey GenesisVestedDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'VestedDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN
-> VerificationKey GenesisVestedDelegateKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey GenesisVestedDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisVestedDelegateKey) where
serialiseToRawBytes :: SigningKey GenesisVestedDelegateKey -> ByteString
serialiseToRawBytes (GenesisVestedDelegateSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisVestedDelegateKey)
-> ByteString -> Maybe (SigningKey GenesisVestedDelegateKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisVestedDelegateKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisVestedDelegateKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisVestedDelegateKey
GenesisVestedDelegateSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey GenesisVestedDelegateKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey GenesisVestedDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisVestedDelegateKey =
GenesisVestedDelegateKeyHash (Sophie.KeyHash Sophie.VestedDelegate StandardCrypto)
deriving stock (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
(Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool)
-> Eq (Hash GenesisVestedDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
$c/= :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
== :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
$c== :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
Eq, Eq (Hash GenesisVestedDelegateKey)
Eq (Hash GenesisVestedDelegateKey)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Ordering)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey)
-> (Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey)
-> Ord (Hash GenesisVestedDelegateKey)
Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Ordering
Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey
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
min :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey
$cmin :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey
max :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey
$cmax :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Hash GenesisVestedDelegateKey
>= :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
$c>= :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
> :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
$c> :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
<= :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
$c<= :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
< :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
$c< :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Bool
compare :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Ordering
$ccompare :: Hash GenesisVestedDelegateKey
-> Hash GenesisVestedDelegateKey -> Ordering
$cp1Ord :: Eq (Hash GenesisVestedDelegateKey)
Ord)
deriving (Int -> Hash GenesisVestedDelegateKey -> ShowS
[Hash GenesisVestedDelegateKey] -> ShowS
Hash GenesisVestedDelegateKey -> String
(Int -> Hash GenesisVestedDelegateKey -> ShowS)
-> (Hash GenesisVestedDelegateKey -> String)
-> ([Hash GenesisVestedDelegateKey] -> ShowS)
-> Show (Hash GenesisVestedDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisVestedDelegateKey] -> ShowS
$cshowList :: [Hash GenesisVestedDelegateKey] -> ShowS
show :: Hash GenesisVestedDelegateKey -> String
$cshow :: Hash GenesisVestedDelegateKey -> String
showsPrec :: Int -> Hash GenesisVestedDelegateKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisVestedDelegateKey -> ShowS
Show, String -> Hash GenesisVestedDelegateKey
(String -> Hash GenesisVestedDelegateKey)
-> IsString (Hash GenesisVestedDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisVestedDelegateKey
$cfromString :: String -> Hash GenesisVestedDelegateKey
IsString) via UsingRawBytesHex (Hash GenesisVestedDelegateKey)
deriving (Typeable (Hash GenesisVestedDelegateKey)
Typeable (Hash GenesisVestedDelegateKey)
-> (Hash GenesisVestedDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateKey] -> Size)
-> ToCBOR (Hash GenesisVestedDelegateKey)
Hash GenesisVestedDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateKey) -> Size
toCBOR :: Hash GenesisVestedDelegateKey -> Encoding
$ctoCBOR :: Hash GenesisVestedDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisVestedDelegateKey)
ToCBOR, Typeable (Hash GenesisVestedDelegateKey)
Decoder s (Hash GenesisVestedDelegateKey)
Typeable (Hash GenesisVestedDelegateKey)
-> (forall s. Decoder s (Hash GenesisVestedDelegateKey))
-> (Proxy (Hash GenesisVestedDelegateKey) -> Text)
-> FromCBOR (Hash GenesisVestedDelegateKey)
Proxy (Hash GenesisVestedDelegateKey) -> Text
forall s. Decoder s (Hash GenesisVestedDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisVestedDelegateKey) -> Text
$clabel :: Proxy (Hash GenesisVestedDelegateKey) -> Text
fromCBOR :: Decoder s (Hash GenesisVestedDelegateKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisVestedDelegateKey)
$cp1FromCBOR :: Typeable (Hash GenesisVestedDelegateKey)
FromCBOR) via UsingRawBytes (Hash GenesisVestedDelegateKey)
deriving anyclass HasTypeProxy (Hash GenesisVestedDelegateKey)
HasTypeProxy (Hash GenesisVestedDelegateKey)
-> (Hash GenesisVestedDelegateKey -> ByteString)
-> (AsType (Hash GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateKey))
-> SerialiseAsCBOR (Hash GenesisVestedDelegateKey)
AsType (Hash GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateKey)
Hash GenesisVestedDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisVestedDelegateKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateKey)
serialiseToCBOR :: Hash GenesisVestedDelegateKey -> ByteString
$cserialiseToCBOR :: Hash GenesisVestedDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisVestedDelegateKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisVestedDelegateKey) where
serialiseToRawBytes :: Hash GenesisVestedDelegateKey -> ByteString
serialiseToRawBytes (GenesisVestedDelegateKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisVestedDelegateKey)
-> ByteString -> Maybe (Hash GenesisVestedDelegateKey)
deserialiseFromRawBytes (AsHash AsGenesisVestedDelegateKey) ByteString
bs =
KeyHash 'VestedDelegate StandardCrypto
-> Hash GenesisVestedDelegateKey
GenesisVestedDelegateKeyHash (KeyHash 'VestedDelegate StandardCrypto
-> Hash GenesisVestedDelegateKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'VestedDelegate StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'VestedDelegate StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedDelegateKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisVestedDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisVestedDelegateKey) where
textEnvelopeType :: AsType (VerificationKey GenesisVestedDelegateKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisVestedDelegateKey)
_ = TextEnvelopeType
"GenesisVestedDelegateVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisVestedDelegateKey) where
textEnvelopeType :: AsType (SigningKey GenesisVestedDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisVestedDelegateKey)
_ = TextEnvelopeType
"GenesisVestedDelegateSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole GenesisVestedDelegateKey StakePoolKey where
castVerificationKey :: VerificationKey GenesisVestedDelegateKey
-> VerificationKey StakePoolKey
castVerificationKey (GenesisVestedDelegateVerificationKey (Sophie.VKey vkey)) =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'StakePool StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole GenesisVestedDelegateKey StakePoolKey where
castSigningKey :: SigningKey GenesisVestedDelegateKey -> SigningKey StakePoolKey
castSigningKey (GenesisVestedDelegateSigningKey skey) =
SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
StakePoolSigningKey SignKeyDSIGN StandardCrypto
skey
data GenesisVestedDelegateExtendedKey
instance HasTypeProxy GenesisVestedDelegateExtendedKey where
data AsType GenesisVestedDelegateExtendedKey = AsGenesisVestedDelegateExtendedKey
proxyToAsType :: Proxy GenesisVestedDelegateExtendedKey
-> AsType GenesisVestedDelegateExtendedKey
proxyToAsType Proxy GenesisVestedDelegateExtendedKey
_ = AsType GenesisVestedDelegateExtendedKey
AsGenesisVestedDelegateExtendedKey
instance Key GenesisVestedDelegateExtendedKey where
newtype VerificationKey GenesisVestedDelegateExtendedKey =
GenesisVestedDelegateExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool
(VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool)
-> (VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool)
-> Eq (VerificationKey GenesisVestedDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool
$c/= :: VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool
== :: VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool
$c== :: VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey GenesisVestedDelegateExtendedKey)
HasTypeProxy (VerificationKey GenesisVestedDelegateExtendedKey)
-> (VerificationKey GenesisVestedDelegateExtendedKey -> ByteString)
-> (AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (VerificationKey GenesisVestedDelegateExtendedKey))
-> SerialiseAsCBOR
(VerificationKey GenesisVestedDelegateExtendedKey)
AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (VerificationKey GenesisVestedDelegateExtendedKey)
VerificationKey GenesisVestedDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (VerificationKey GenesisVestedDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (VerificationKey GenesisVestedDelegateExtendedKey)
serialiseToCBOR :: VerificationKey GenesisVestedDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey GenesisVestedDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey GenesisVestedDelegateExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey GenesisVestedDelegateExtendedKey -> ShowS
[VerificationKey GenesisVestedDelegateExtendedKey] -> ShowS
VerificationKey GenesisVestedDelegateExtendedKey -> String
(Int -> VerificationKey GenesisVestedDelegateExtendedKey -> ShowS)
-> (VerificationKey GenesisVestedDelegateExtendedKey -> String)
-> ([VerificationKey GenesisVestedDelegateExtendedKey] -> ShowS)
-> Show (VerificationKey GenesisVestedDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey GenesisVestedDelegateExtendedKey] -> ShowS
$cshowList :: [VerificationKey GenesisVestedDelegateExtendedKey] -> ShowS
show :: VerificationKey GenesisVestedDelegateExtendedKey -> String
$cshow :: VerificationKey GenesisVestedDelegateExtendedKey -> String
showsPrec :: Int -> VerificationKey GenesisVestedDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey GenesisVestedDelegateExtendedKey -> ShowS
Show, String -> VerificationKey GenesisVestedDelegateExtendedKey
(String -> VerificationKey GenesisVestedDelegateExtendedKey)
-> IsString (VerificationKey GenesisVestedDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisVestedDelegateExtendedKey
$cfromString :: String -> VerificationKey GenesisVestedDelegateExtendedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisVestedDelegateExtendedKey)
newtype SigningKey GenesisVestedDelegateExtendedKey =
GenesisVestedDelegateExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey GenesisVestedDelegateExtendedKey)
HasTypeProxy (SigningKey GenesisVestedDelegateExtendedKey)
-> (SigningKey GenesisVestedDelegateExtendedKey -> ByteString)
-> (AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (SigningKey GenesisVestedDelegateExtendedKey))
-> SerialiseAsCBOR (SigningKey GenesisVestedDelegateExtendedKey)
AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (SigningKey GenesisVestedDelegateExtendedKey)
SigningKey GenesisVestedDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (SigningKey GenesisVestedDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either
DecoderError (SigningKey GenesisVestedDelegateExtendedKey)
serialiseToCBOR :: SigningKey GenesisVestedDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey GenesisVestedDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey GenesisVestedDelegateExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey GenesisVestedDelegateExtendedKey -> ShowS
[SigningKey GenesisVestedDelegateExtendedKey] -> ShowS
SigningKey GenesisVestedDelegateExtendedKey -> String
(Int -> SigningKey GenesisVestedDelegateExtendedKey -> ShowS)
-> (SigningKey GenesisVestedDelegateExtendedKey -> String)
-> ([SigningKey GenesisVestedDelegateExtendedKey] -> ShowS)
-> Show (SigningKey GenesisVestedDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey GenesisVestedDelegateExtendedKey] -> ShowS
$cshowList :: [SigningKey GenesisVestedDelegateExtendedKey] -> ShowS
show :: SigningKey GenesisVestedDelegateExtendedKey -> String
$cshow :: SigningKey GenesisVestedDelegateExtendedKey -> String
showsPrec :: Int -> SigningKey GenesisVestedDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey GenesisVestedDelegateExtendedKey -> ShowS
Show, String -> SigningKey GenesisVestedDelegateExtendedKey
(String -> SigningKey GenesisVestedDelegateExtendedKey)
-> IsString (SigningKey GenesisVestedDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisVestedDelegateExtendedKey
$cfromString :: String -> SigningKey GenesisVestedDelegateExtendedKey
IsString) via UsingRawBytesHex (SigningKey GenesisVestedDelegateExtendedKey)
deterministicSigningKey :: AsType GenesisVestedDelegateExtendedKey
-> Crypto.Seed
-> SigningKey GenesisVestedDelegateExtendedKey
deterministicSigningKey :: AsType GenesisVestedDelegateExtendedKey
-> Seed -> SigningKey GenesisVestedDelegateExtendedKey
deterministicSigningKey AsType GenesisVestedDelegateExtendedKey
AsGenesisVestedDelegateExtendedKey Seed
seed =
XPrv -> SigningKey GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType GenesisVestedDelegateExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisVestedDelegateExtendedKey -> Word
deterministicSigningKeySeedSize AsType GenesisVestedDelegateExtendedKey
AsGenesisVestedDelegateExtendedKey = Word
32
getVerificationKey :: SigningKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey
getVerificationKey :: SigningKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateExtendedKey
getVerificationKey (GenesisVestedDelegateExtendedSigningKey sk) =
XPub -> VerificationKey GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
verificationKeyHash :: VerificationKey GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
verificationKeyHash (GenesisVestedDelegateExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto
-> Hash GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedKeyHash
(KeyHash 'Staking StandardCrypto
-> Hash GenesisVestedDelegateExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash GenesisVestedDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash GenesisVestedDelegateExtendedKey)
-> Hash Blake2b_224 XPub -> Hash GenesisVestedDelegateExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey GenesisVestedDelegateExtendedKey) where
toCBOR :: VerificationKey GenesisVestedDelegateExtendedKey -> Encoding
toCBOR (GenesisVestedDelegateExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey GenesisVestedDelegateExtendedKey) where
fromCBOR :: Decoder s (VerificationKey GenesisVestedDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey))
-> (XPub
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey GenesisVestedDelegateExtendedKey
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey GenesisVestedDelegateExtendedKey
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey))
-> (XPub -> VerificationKey GenesisVestedDelegateExtendedKey)
-> XPub
-> Decoder s (VerificationKey GenesisVestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey GenesisVestedDelegateExtendedKey) where
toCBOR :: SigningKey GenesisVestedDelegateExtendedKey -> Encoding
toCBOR (GenesisVestedDelegateExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey GenesisVestedDelegateExtendedKey) where
fromCBOR :: Decoder s (SigningKey GenesisVestedDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey GenesisVestedDelegateExtendedKey))
-> (XPrv
-> Decoder s (SigningKey GenesisVestedDelegateExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey GenesisVestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey GenesisVestedDelegateExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey GenesisVestedDelegateExtendedKey
-> Decoder s (SigningKey GenesisVestedDelegateExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey GenesisVestedDelegateExtendedKey
-> Decoder s (SigningKey GenesisVestedDelegateExtendedKey))
-> (XPrv -> SigningKey GenesisVestedDelegateExtendedKey)
-> XPrv
-> Decoder s (SigningKey GenesisVestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey GenesisVestedDelegateExtendedKey) where
serialiseToRawBytes :: VerificationKey GenesisVestedDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisVestedDelegateExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsGenesisVestedDelegateExtendedKey) ByteString
bs =
(String
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey))
-> (XPub
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
-> String
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey GenesisVestedDelegateExtendedKey
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey GenesisVestedDelegateExtendedKey
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey))
-> (XPub -> VerificationKey GenesisVestedDelegateExtendedKey)
-> XPub
-> Maybe (VerificationKey GenesisVestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey GenesisVestedDelegateExtendedKey) where
serialiseToRawBytes :: SigningKey GenesisVestedDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisVestedDelegateExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> ByteString
-> Maybe (SigningKey GenesisVestedDelegateExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsGenesisVestedDelegateExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey GenesisVestedDelegateExtendedKey))
-> (XPrv -> Maybe (SigningKey GenesisVestedDelegateExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey GenesisVestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey GenesisVestedDelegateExtendedKey)
-> String -> Maybe (SigningKey GenesisVestedDelegateExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey GenesisVestedDelegateExtendedKey)
forall a. Maybe a
Nothing) (SigningKey GenesisVestedDelegateExtendedKey
-> Maybe (SigningKey GenesisVestedDelegateExtendedKey)
forall a. a -> Maybe a
Just (SigningKey GenesisVestedDelegateExtendedKey
-> Maybe (SigningKey GenesisVestedDelegateExtendedKey))
-> (XPrv -> SigningKey GenesisVestedDelegateExtendedKey)
-> XPrv
-> Maybe (SigningKey GenesisVestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
newtype instance Hash GenesisVestedDelegateExtendedKey =
GenesisVestedDelegateExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
(Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool)
-> Eq (Hash GenesisVestedDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
$c/= :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
== :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
$c== :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
Eq, Eq (Hash GenesisVestedDelegateExtendedKey)
Eq (Hash GenesisVestedDelegateExtendedKey)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Ordering)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey)
-> (Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey)
-> Ord (Hash GenesisVestedDelegateExtendedKey)
Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Ordering
Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
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
min :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
$cmin :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
max :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
$cmax :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey
>= :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
$c>= :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
> :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
$c> :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
<= :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
$c<= :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
< :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
$c< :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Bool
compare :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Ordering
$ccompare :: Hash GenesisVestedDelegateExtendedKey
-> Hash GenesisVestedDelegateExtendedKey -> Ordering
$cp1Ord :: Eq (Hash GenesisVestedDelegateExtendedKey)
Ord)
deriving (Int -> Hash GenesisVestedDelegateExtendedKey -> ShowS
[Hash GenesisVestedDelegateExtendedKey] -> ShowS
Hash GenesisVestedDelegateExtendedKey -> String
(Int -> Hash GenesisVestedDelegateExtendedKey -> ShowS)
-> (Hash GenesisVestedDelegateExtendedKey -> String)
-> ([Hash GenesisVestedDelegateExtendedKey] -> ShowS)
-> Show (Hash GenesisVestedDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash GenesisVestedDelegateExtendedKey] -> ShowS
$cshowList :: [Hash GenesisVestedDelegateExtendedKey] -> ShowS
show :: Hash GenesisVestedDelegateExtendedKey -> String
$cshow :: Hash GenesisVestedDelegateExtendedKey -> String
showsPrec :: Int -> Hash GenesisVestedDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash GenesisVestedDelegateExtendedKey -> ShowS
Show, String -> Hash GenesisVestedDelegateExtendedKey
(String -> Hash GenesisVestedDelegateExtendedKey)
-> IsString (Hash GenesisVestedDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisVestedDelegateExtendedKey
$cfromString :: String -> Hash GenesisVestedDelegateExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisVestedDelegateExtendedKey)
deriving (Typeable (Hash GenesisVestedDelegateExtendedKey)
Typeable (Hash GenesisVestedDelegateExtendedKey)
-> (Hash GenesisVestedDelegateExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateExtendedKey] -> Size)
-> ToCBOR (Hash GenesisVestedDelegateExtendedKey)
Hash GenesisVestedDelegateExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisVestedDelegateExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisVestedDelegateExtendedKey) -> Size
toCBOR :: Hash GenesisVestedDelegateExtendedKey -> Encoding
$ctoCBOR :: Hash GenesisVestedDelegateExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash GenesisVestedDelegateExtendedKey)
ToCBOR, Typeable (Hash GenesisVestedDelegateExtendedKey)
Decoder s (Hash GenesisVestedDelegateExtendedKey)
Typeable (Hash GenesisVestedDelegateExtendedKey)
-> (forall s. Decoder s (Hash GenesisVestedDelegateExtendedKey))
-> (Proxy (Hash GenesisVestedDelegateExtendedKey) -> Text)
-> FromCBOR (Hash GenesisVestedDelegateExtendedKey)
Proxy (Hash GenesisVestedDelegateExtendedKey) -> Text
forall s. Decoder s (Hash GenesisVestedDelegateExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash GenesisVestedDelegateExtendedKey) -> Text
$clabel :: Proxy (Hash GenesisVestedDelegateExtendedKey) -> Text
fromCBOR :: Decoder s (Hash GenesisVestedDelegateExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisVestedDelegateExtendedKey)
$cp1FromCBOR :: Typeable (Hash GenesisVestedDelegateExtendedKey)
FromCBOR) via UsingRawBytes (Hash GenesisVestedDelegateExtendedKey)
deriving anyclass HasTypeProxy (Hash GenesisVestedDelegateExtendedKey)
HasTypeProxy (Hash GenesisVestedDelegateExtendedKey)
-> (Hash GenesisVestedDelegateExtendedKey -> ByteString)
-> (AsType (Hash GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateExtendedKey))
-> SerialiseAsCBOR (Hash GenesisVestedDelegateExtendedKey)
AsType (Hash GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateExtendedKey)
Hash GenesisVestedDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash GenesisVestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisVestedDelegateExtendedKey)
serialiseToCBOR :: Hash GenesisVestedDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: Hash GenesisVestedDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash GenesisVestedDelegateExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisVestedDelegateExtendedKey) where
serialiseToRawBytes :: Hash GenesisVestedDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisVestedDelegateExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisVestedDelegateExtendedKey)
-> ByteString -> Maybe (Hash GenesisVestedDelegateExtendedKey)
deserialiseFromRawBytes (AsHash AsGenesisVestedDelegateExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto
-> Hash GenesisVestedDelegateExtendedKey
GenesisVestedDelegateExtendedKeyHash (KeyHash 'Staking StandardCrypto
-> Hash GenesisVestedDelegateExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash GenesisVestedDelegateExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash GenesisVestedDelegateExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey GenesisVestedDelegateExtendedKey) where
textEnvelopeType :: AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisVestedDelegateExtendedKey)
_ = TextEnvelopeType
"GenesisVestedDelegateExtendedVerificationKey_ed25519_bip32"
instance HasTextEnvelope (SigningKey GenesisVestedDelegateExtendedKey) where
textEnvelopeType :: AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisVestedDelegateExtendedKey)
_ = TextEnvelopeType
"GenesisVestedDelegateExtendedSigningKey_ed25519_bip32"
instance CastVerificationKeyRole GenesisVestedDelegateExtendedKey GenesisVestedDelegateKey where
castVerificationKey :: VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateKey
castVerificationKey (GenesisVestedDelegateExtendedVerificationKey vk) =
VKey 'VestedDelegate StandardCrypto
-> VerificationKey GenesisVestedDelegateKey
GenesisVestedDelegateVerificationKey
(VKey 'VestedDelegate StandardCrypto
-> VerificationKey GenesisVestedDelegateKey)
-> (XPub -> VKey 'VestedDelegate StandardCrypto)
-> XPub
-> VerificationKey GenesisVestedDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'VestedDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'VestedDelegate StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'VestedDelegate StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey GenesisVestedDelegateKey)
-> XPub -> VerificationKey GenesisVestedDelegateKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data VestedKey
instance HasTypeProxy VestedKey where
data AsType VestedKey = AsVestedKey
proxyToAsType :: Proxy VestedKey -> AsType VestedKey
proxyToAsType Proxy VestedKey
_ = AsType VestedKey
AsVestedKey
instance Key VestedKey where
newtype VerificationKey VestedKey =
VestedVerificationKey (Sophie.VKey Sophie.Vested StandardCrypto)
deriving stock (VerificationKey VestedKey -> VerificationKey VestedKey -> Bool
(VerificationKey VestedKey -> VerificationKey VestedKey -> Bool)
-> (VerificationKey VestedKey -> VerificationKey VestedKey -> Bool)
-> Eq (VerificationKey VestedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey VestedKey -> VerificationKey VestedKey -> Bool
$c/= :: VerificationKey VestedKey -> VerificationKey VestedKey -> Bool
== :: VerificationKey VestedKey -> VerificationKey VestedKey -> Bool
$c== :: VerificationKey VestedKey -> VerificationKey VestedKey -> Bool
Eq)
deriving (Int -> VerificationKey VestedKey -> ShowS
[VerificationKey VestedKey] -> ShowS
VerificationKey VestedKey -> String
(Int -> VerificationKey VestedKey -> ShowS)
-> (VerificationKey VestedKey -> String)
-> ([VerificationKey VestedKey] -> ShowS)
-> Show (VerificationKey VestedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey VestedKey] -> ShowS
$cshowList :: [VerificationKey VestedKey] -> ShowS
show :: VerificationKey VestedKey -> String
$cshow :: VerificationKey VestedKey -> String
showsPrec :: Int -> VerificationKey VestedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey VestedKey -> ShowS
Show, String -> VerificationKey VestedKey
(String -> VerificationKey VestedKey)
-> IsString (VerificationKey VestedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey VestedKey
$cfromString :: String -> VerificationKey VestedKey
IsString) via UsingRawBytesHex (VerificationKey VestedKey)
deriving newtype (Typeable (VerificationKey VestedKey)
Typeable (VerificationKey VestedKey)
-> (VerificationKey VestedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedKey] -> Size)
-> ToCBOR (VerificationKey VestedKey)
VerificationKey VestedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedKey) -> Size
toCBOR :: VerificationKey VestedKey -> Encoding
$ctoCBOR :: VerificationKey VestedKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey VestedKey)
ToCBOR, Typeable (VerificationKey VestedKey)
Decoder s (VerificationKey VestedKey)
Typeable (VerificationKey VestedKey)
-> (forall s. Decoder s (VerificationKey VestedKey))
-> (Proxy (VerificationKey VestedKey) -> Text)
-> FromCBOR (VerificationKey VestedKey)
Proxy (VerificationKey VestedKey) -> Text
forall s. Decoder s (VerificationKey VestedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey VestedKey) -> Text
$clabel :: Proxy (VerificationKey VestedKey) -> Text
fromCBOR :: Decoder s (VerificationKey VestedKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey VestedKey)
$cp1FromCBOR :: Typeable (VerificationKey VestedKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey VestedKey)
HasTypeProxy (VerificationKey VestedKey)
-> (VerificationKey VestedKey -> ByteString)
-> (AsType (VerificationKey VestedKey)
-> ByteString -> Either DecoderError (VerificationKey VestedKey))
-> SerialiseAsCBOR (VerificationKey VestedKey)
AsType (VerificationKey VestedKey)
-> ByteString -> Either DecoderError (VerificationKey VestedKey)
VerificationKey VestedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey VestedKey)
-> ByteString -> Either DecoderError (VerificationKey VestedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey VestedKey)
-> ByteString -> Either DecoderError (VerificationKey VestedKey)
serialiseToCBOR :: VerificationKey VestedKey -> ByteString
$cserialiseToCBOR :: VerificationKey VestedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey VestedKey)
SerialiseAsCBOR
newtype SigningKey VestedKey =
VestedSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey VestedKey -> ShowS
[SigningKey VestedKey] -> ShowS
SigningKey VestedKey -> String
(Int -> SigningKey VestedKey -> ShowS)
-> (SigningKey VestedKey -> String)
-> ([SigningKey VestedKey] -> ShowS)
-> Show (SigningKey VestedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey VestedKey] -> ShowS
$cshowList :: [SigningKey VestedKey] -> ShowS
show :: SigningKey VestedKey -> String
$cshow :: SigningKey VestedKey -> String
showsPrec :: Int -> SigningKey VestedKey -> ShowS
$cshowsPrec :: Int -> SigningKey VestedKey -> ShowS
Show, String -> SigningKey VestedKey
(String -> SigningKey VestedKey) -> IsString (SigningKey VestedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey VestedKey
$cfromString :: String -> SigningKey VestedKey
IsString) via UsingRawBytesHex (SigningKey VestedKey)
deriving newtype (Typeable (SigningKey VestedKey)
Typeable (SigningKey VestedKey)
-> (SigningKey VestedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedKey] -> Size)
-> ToCBOR (SigningKey VestedKey)
SigningKey VestedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedKey) -> Size
toCBOR :: SigningKey VestedKey -> Encoding
$ctoCBOR :: SigningKey VestedKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey VestedKey)
ToCBOR, Typeable (SigningKey VestedKey)
Decoder s (SigningKey VestedKey)
Typeable (SigningKey VestedKey)
-> (forall s. Decoder s (SigningKey VestedKey))
-> (Proxy (SigningKey VestedKey) -> Text)
-> FromCBOR (SigningKey VestedKey)
Proxy (SigningKey VestedKey) -> Text
forall s. Decoder s (SigningKey VestedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey VestedKey) -> Text
$clabel :: Proxy (SigningKey VestedKey) -> Text
fromCBOR :: Decoder s (SigningKey VestedKey)
$cfromCBOR :: forall s. Decoder s (SigningKey VestedKey)
$cp1FromCBOR :: Typeable (SigningKey VestedKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey VestedKey)
HasTypeProxy (SigningKey VestedKey)
-> (SigningKey VestedKey -> ByteString)
-> (AsType (SigningKey VestedKey)
-> ByteString -> Either DecoderError (SigningKey VestedKey))
-> SerialiseAsCBOR (SigningKey VestedKey)
AsType (SigningKey VestedKey)
-> ByteString -> Either DecoderError (SigningKey VestedKey)
SigningKey VestedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey VestedKey)
-> ByteString -> Either DecoderError (SigningKey VestedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey VestedKey)
-> ByteString -> Either DecoderError (SigningKey VestedKey)
serialiseToCBOR :: SigningKey VestedKey -> ByteString
$cserialiseToCBOR :: SigningKey VestedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey VestedKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType VestedKey -> Crypto.Seed -> SigningKey VestedKey
deterministicSigningKey :: AsType VestedKey -> Seed -> SigningKey VestedKey
deterministicSigningKey AsType VestedKey
AsVestedKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey VestedKey
VestedSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType VestedKey -> Word
deterministicSigningKeySeedSize :: AsType VestedKey -> Word
deterministicSigningKeySeedSize AsType VestedKey
AsVestedKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey VestedKey -> VerificationKey VestedKey
getVerificationKey :: SigningKey VestedKey -> VerificationKey VestedKey
getVerificationKey (VestedSigningKey sk) =
VKey 'Vested StandardCrypto -> VerificationKey VestedKey
VestedVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Vested StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey VestedKey -> Hash VestedKey
verificationKeyHash :: VerificationKey VestedKey -> Hash VestedKey
verificationKeyHash (VestedVerificationKey vkey) =
KeyHash 'Vested StandardCrypto -> Hash VestedKey
VestedKeyHash (VKey 'Vested StandardCrypto -> KeyHash 'Vested StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'Vested StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey VestedKey) where
serialiseToRawBytes :: VerificationKey VestedKey -> ByteString
serialiseToRawBytes (VestedVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey VestedKey)
-> ByteString -> Maybe (VerificationKey VestedKey)
deserialiseFromRawBytes (AsVerificationKey AsVestedKey) ByteString
bs =
VKey 'Vested StandardCrypto -> VerificationKey VestedKey
VestedVerificationKey (VKey 'Vested StandardCrypto -> VerificationKey VestedKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'Vested StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey VestedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Vested StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey VestedKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey VestedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey VestedKey) where
serialiseToRawBytes :: SigningKey VestedKey -> ByteString
serialiseToRawBytes (VestedSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey VestedKey)
-> ByteString -> Maybe (SigningKey VestedKey)
deserialiseFromRawBytes (AsSigningKey AsVestedKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey VestedKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey VestedKey
VestedSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey VestedKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey VestedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash VestedKey =
VestedKeyHash (Sophie.KeyHash Sophie.Vested StandardCrypto)
deriving stock (Hash VestedKey -> Hash VestedKey -> Bool
(Hash VestedKey -> Hash VestedKey -> Bool)
-> (Hash VestedKey -> Hash VestedKey -> Bool)
-> Eq (Hash VestedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash VestedKey -> Hash VestedKey -> Bool
$c/= :: Hash VestedKey -> Hash VestedKey -> Bool
== :: Hash VestedKey -> Hash VestedKey -> Bool
$c== :: Hash VestedKey -> Hash VestedKey -> Bool
Eq, Eq (Hash VestedKey)
Eq (Hash VestedKey)
-> (Hash VestedKey -> Hash VestedKey -> Ordering)
-> (Hash VestedKey -> Hash VestedKey -> Bool)
-> (Hash VestedKey -> Hash VestedKey -> Bool)
-> (Hash VestedKey -> Hash VestedKey -> Bool)
-> (Hash VestedKey -> Hash VestedKey -> Bool)
-> (Hash VestedKey -> Hash VestedKey -> Hash VestedKey)
-> (Hash VestedKey -> Hash VestedKey -> Hash VestedKey)
-> Ord (Hash VestedKey)
Hash VestedKey -> Hash VestedKey -> Bool
Hash VestedKey -> Hash VestedKey -> Ordering
Hash VestedKey -> Hash VestedKey -> Hash VestedKey
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
min :: Hash VestedKey -> Hash VestedKey -> Hash VestedKey
$cmin :: Hash VestedKey -> Hash VestedKey -> Hash VestedKey
max :: Hash VestedKey -> Hash VestedKey -> Hash VestedKey
$cmax :: Hash VestedKey -> Hash VestedKey -> Hash VestedKey
>= :: Hash VestedKey -> Hash VestedKey -> Bool
$c>= :: Hash VestedKey -> Hash VestedKey -> Bool
> :: Hash VestedKey -> Hash VestedKey -> Bool
$c> :: Hash VestedKey -> Hash VestedKey -> Bool
<= :: Hash VestedKey -> Hash VestedKey -> Bool
$c<= :: Hash VestedKey -> Hash VestedKey -> Bool
< :: Hash VestedKey -> Hash VestedKey -> Bool
$c< :: Hash VestedKey -> Hash VestedKey -> Bool
compare :: Hash VestedKey -> Hash VestedKey -> Ordering
$ccompare :: Hash VestedKey -> Hash VestedKey -> Ordering
$cp1Ord :: Eq (Hash VestedKey)
Ord)
deriving (Int -> Hash VestedKey -> ShowS
[Hash VestedKey] -> ShowS
Hash VestedKey -> String
(Int -> Hash VestedKey -> ShowS)
-> (Hash VestedKey -> String)
-> ([Hash VestedKey] -> ShowS)
-> Show (Hash VestedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash VestedKey] -> ShowS
$cshowList :: [Hash VestedKey] -> ShowS
show :: Hash VestedKey -> String
$cshow :: Hash VestedKey -> String
showsPrec :: Int -> Hash VestedKey -> ShowS
$cshowsPrec :: Int -> Hash VestedKey -> ShowS
Show, String -> Hash VestedKey
(String -> Hash VestedKey) -> IsString (Hash VestedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash VestedKey
$cfromString :: String -> Hash VestedKey
IsString) via UsingRawBytesHex (Hash VestedKey)
deriving (Typeable (Hash VestedKey)
Typeable (Hash VestedKey)
-> (Hash VestedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedKey] -> Size)
-> ToCBOR (Hash VestedKey)
Hash VestedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedKey) -> Size
toCBOR :: Hash VestedKey -> Encoding
$ctoCBOR :: Hash VestedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash VestedKey)
ToCBOR, Typeable (Hash VestedKey)
Decoder s (Hash VestedKey)
Typeable (Hash VestedKey)
-> (forall s. Decoder s (Hash VestedKey))
-> (Proxy (Hash VestedKey) -> Text)
-> FromCBOR (Hash VestedKey)
Proxy (Hash VestedKey) -> Text
forall s. Decoder s (Hash VestedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash VestedKey) -> Text
$clabel :: Proxy (Hash VestedKey) -> Text
fromCBOR :: Decoder s (Hash VestedKey)
$cfromCBOR :: forall s. Decoder s (Hash VestedKey)
$cp1FromCBOR :: Typeable (Hash VestedKey)
FromCBOR) via UsingRawBytes (Hash VestedKey)
deriving anyclass HasTypeProxy (Hash VestedKey)
HasTypeProxy (Hash VestedKey)
-> (Hash VestedKey -> ByteString)
-> (AsType (Hash VestedKey)
-> ByteString -> Either DecoderError (Hash VestedKey))
-> SerialiseAsCBOR (Hash VestedKey)
AsType (Hash VestedKey)
-> ByteString -> Either DecoderError (Hash VestedKey)
Hash VestedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash VestedKey)
-> ByteString -> Either DecoderError (Hash VestedKey)
$cdeserialiseFromCBOR :: AsType (Hash VestedKey)
-> ByteString -> Either DecoderError (Hash VestedKey)
serialiseToCBOR :: Hash VestedKey -> ByteString
$cserialiseToCBOR :: Hash VestedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash VestedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash VestedKey) where
serialiseToRawBytes :: Hash VestedKey -> ByteString
serialiseToRawBytes (VestedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash VestedKey) -> ByteString -> Maybe (Hash VestedKey)
deserialiseFromRawBytes (AsHash AsVestedKey) ByteString
bs =
KeyHash 'Vested StandardCrypto -> Hash VestedKey
VestedKeyHash (KeyHash 'Vested StandardCrypto -> Hash VestedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Vested StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Vested StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> Hash VestedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash VestedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey VestedKey) where
textEnvelopeType :: AsType (VerificationKey VestedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey VestedKey)
_ = TextEnvelopeType
"VestedVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey VestedKey) where
textEnvelopeType :: AsType (SigningKey VestedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey VestedKey)
_ = TextEnvelopeType
"VestedSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
data VestedExtendedKey
instance HasTypeProxy VestedExtendedKey where
data AsType VestedExtendedKey = AsVestedExtendedKey
proxyToAsType :: Proxy VestedExtendedKey -> AsType VestedExtendedKey
proxyToAsType Proxy VestedExtendedKey
_ = AsType VestedExtendedKey
AsVestedExtendedKey
instance Key VestedExtendedKey where
newtype VerificationKey VestedExtendedKey =
VestedExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool
(VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool)
-> (VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool)
-> Eq (VerificationKey VestedExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool
$c/= :: VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool
== :: VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool
$c== :: VerificationKey VestedExtendedKey
-> VerificationKey VestedExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey VestedExtendedKey)
HasTypeProxy (VerificationKey VestedExtendedKey)
-> (VerificationKey VestedExtendedKey -> ByteString)
-> (AsType (VerificationKey VestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedExtendedKey))
-> SerialiseAsCBOR (VerificationKey VestedExtendedKey)
AsType (VerificationKey VestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedExtendedKey)
VerificationKey VestedExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey VestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey VestedExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedExtendedKey)
serialiseToCBOR :: VerificationKey VestedExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey VestedExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey VestedExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey VestedExtendedKey -> ShowS
[VerificationKey VestedExtendedKey] -> ShowS
VerificationKey VestedExtendedKey -> String
(Int -> VerificationKey VestedExtendedKey -> ShowS)
-> (VerificationKey VestedExtendedKey -> String)
-> ([VerificationKey VestedExtendedKey] -> ShowS)
-> Show (VerificationKey VestedExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey VestedExtendedKey] -> ShowS
$cshowList :: [VerificationKey VestedExtendedKey] -> ShowS
show :: VerificationKey VestedExtendedKey -> String
$cshow :: VerificationKey VestedExtendedKey -> String
showsPrec :: Int -> VerificationKey VestedExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey VestedExtendedKey -> ShowS
Show, String -> VerificationKey VestedExtendedKey
(String -> VerificationKey VestedExtendedKey)
-> IsString (VerificationKey VestedExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey VestedExtendedKey
$cfromString :: String -> VerificationKey VestedExtendedKey
IsString) via UsingRawBytesHex (VerificationKey VestedExtendedKey)
newtype SigningKey VestedExtendedKey =
VestedExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey VestedExtendedKey)
HasTypeProxy (SigningKey VestedExtendedKey)
-> (SigningKey VestedExtendedKey -> ByteString)
-> (AsType (SigningKey VestedExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey VestedExtendedKey))
-> SerialiseAsCBOR (SigningKey VestedExtendedKey)
AsType (SigningKey VestedExtendedKey)
-> ByteString -> Either DecoderError (SigningKey VestedExtendedKey)
SigningKey VestedExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey VestedExtendedKey)
-> ByteString -> Either DecoderError (SigningKey VestedExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey VestedExtendedKey)
-> ByteString -> Either DecoderError (SigningKey VestedExtendedKey)
serialiseToCBOR :: SigningKey VestedExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey VestedExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey VestedExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey VestedExtendedKey -> ShowS
[SigningKey VestedExtendedKey] -> ShowS
SigningKey VestedExtendedKey -> String
(Int -> SigningKey VestedExtendedKey -> ShowS)
-> (SigningKey VestedExtendedKey -> String)
-> ([SigningKey VestedExtendedKey] -> ShowS)
-> Show (SigningKey VestedExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey VestedExtendedKey] -> ShowS
$cshowList :: [SigningKey VestedExtendedKey] -> ShowS
show :: SigningKey VestedExtendedKey -> String
$cshow :: SigningKey VestedExtendedKey -> String
showsPrec :: Int -> SigningKey VestedExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey VestedExtendedKey -> ShowS
Show, String -> SigningKey VestedExtendedKey
(String -> SigningKey VestedExtendedKey)
-> IsString (SigningKey VestedExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey VestedExtendedKey
$cfromString :: String -> SigningKey VestedExtendedKey
IsString) via UsingRawBytesHex (SigningKey VestedExtendedKey)
deterministicSigningKey :: AsType VestedExtendedKey
-> Crypto.Seed
-> SigningKey VestedExtendedKey
deterministicSigningKey :: AsType VestedExtendedKey -> Seed -> SigningKey VestedExtendedKey
deterministicSigningKey AsType VestedExtendedKey
AsVestedExtendedKey Seed
seed =
XPrv -> SigningKey VestedExtendedKey
VestedExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType VestedExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType VestedExtendedKey -> Word
deterministicSigningKeySeedSize AsType VestedExtendedKey
AsVestedExtendedKey = Word
32
getVerificationKey :: SigningKey VestedExtendedKey
-> VerificationKey VestedExtendedKey
getVerificationKey :: SigningKey VestedExtendedKey -> VerificationKey VestedExtendedKey
getVerificationKey (VestedExtendedSigningKey sk) =
XPub -> VerificationKey VestedExtendedKey
VestedExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey VestedExtendedKey
-> Hash VestedExtendedKey
verificationKeyHash :: VerificationKey VestedExtendedKey -> Hash VestedExtendedKey
verificationKeyHash (VestedExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto -> Hash VestedExtendedKey
VestedExtendedKeyHash
(KeyHash 'Staking StandardCrypto -> Hash VestedExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash VestedExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash VestedExtendedKey)
-> Hash Blake2b_224 XPub -> Hash VestedExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey VestedExtendedKey) where
toCBOR :: VerificationKey VestedExtendedKey -> Encoding
toCBOR (VestedExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey VestedExtendedKey) where
fromCBOR :: Decoder s (VerificationKey VestedExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey VestedExtendedKey))
-> (XPub -> Decoder s (VerificationKey VestedExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey VestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey VestedExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey VestedExtendedKey
-> Decoder s (VerificationKey VestedExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey VestedExtendedKey
-> Decoder s (VerificationKey VestedExtendedKey))
-> (XPub -> VerificationKey VestedExtendedKey)
-> XPub
-> Decoder s (VerificationKey VestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey VestedExtendedKey
VestedExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey VestedExtendedKey) where
toCBOR :: SigningKey VestedExtendedKey -> Encoding
toCBOR (VestedExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey VestedExtendedKey) where
fromCBOR :: Decoder s (SigningKey VestedExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey VestedExtendedKey))
-> (XPrv -> Decoder s (SigningKey VestedExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey VestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey VestedExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey VestedExtendedKey
-> Decoder s (SigningKey VestedExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey VestedExtendedKey
-> Decoder s (SigningKey VestedExtendedKey))
-> (XPrv -> SigningKey VestedExtendedKey)
-> XPrv
-> Decoder s (SigningKey VestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey VestedExtendedKey
VestedExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey VestedExtendedKey) where
serialiseToRawBytes :: VerificationKey VestedExtendedKey -> ByteString
serialiseToRawBytes (VestedExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey VestedExtendedKey)
-> ByteString -> Maybe (VerificationKey VestedExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsVestedExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey VestedExtendedKey))
-> (XPub -> Maybe (VerificationKey VestedExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey VestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey VestedExtendedKey)
-> String -> Maybe (VerificationKey VestedExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey VestedExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey VestedExtendedKey
-> Maybe (VerificationKey VestedExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey VestedExtendedKey
-> Maybe (VerificationKey VestedExtendedKey))
-> (XPub -> VerificationKey VestedExtendedKey)
-> XPub
-> Maybe (VerificationKey VestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey VestedExtendedKey
VestedExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey VestedExtendedKey) where
serialiseToRawBytes :: SigningKey VestedExtendedKey -> ByteString
serialiseToRawBytes (VestedExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey VestedExtendedKey)
-> ByteString -> Maybe (SigningKey VestedExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsVestedExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey VestedExtendedKey))
-> (XPrv -> Maybe (SigningKey VestedExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey VestedExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey VestedExtendedKey)
-> String -> Maybe (SigningKey VestedExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey VestedExtendedKey)
forall a. Maybe a
Nothing) (SigningKey VestedExtendedKey
-> Maybe (SigningKey VestedExtendedKey)
forall a. a -> Maybe a
Just (SigningKey VestedExtendedKey
-> Maybe (SigningKey VestedExtendedKey))
-> (XPrv -> SigningKey VestedExtendedKey)
-> XPrv
-> Maybe (SigningKey VestedExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey VestedExtendedKey
VestedExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
newtype instance Hash VestedExtendedKey =
VestedExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
(Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool)
-> (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool)
-> Eq (Hash VestedExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
$c/= :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
== :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
$c== :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
Eq, Eq (Hash VestedExtendedKey)
Eq (Hash VestedExtendedKey)
-> (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Ordering)
-> (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool)
-> (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool)
-> (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool)
-> (Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool)
-> (Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey)
-> (Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey)
-> Ord (Hash VestedExtendedKey)
Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
Hash VestedExtendedKey -> Hash VestedExtendedKey -> Ordering
Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey
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
min :: Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey
$cmin :: Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey
max :: Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey
$cmax :: Hash VestedExtendedKey
-> Hash VestedExtendedKey -> Hash VestedExtendedKey
>= :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
$c>= :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
> :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
$c> :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
<= :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
$c<= :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
< :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
$c< :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Bool
compare :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Ordering
$ccompare :: Hash VestedExtendedKey -> Hash VestedExtendedKey -> Ordering
$cp1Ord :: Eq (Hash VestedExtendedKey)
Ord)
deriving (Int -> Hash VestedExtendedKey -> ShowS
[Hash VestedExtendedKey] -> ShowS
Hash VestedExtendedKey -> String
(Int -> Hash VestedExtendedKey -> ShowS)
-> (Hash VestedExtendedKey -> String)
-> ([Hash VestedExtendedKey] -> ShowS)
-> Show (Hash VestedExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash VestedExtendedKey] -> ShowS
$cshowList :: [Hash VestedExtendedKey] -> ShowS
show :: Hash VestedExtendedKey -> String
$cshow :: Hash VestedExtendedKey -> String
showsPrec :: Int -> Hash VestedExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash VestedExtendedKey -> ShowS
Show, String -> Hash VestedExtendedKey
(String -> Hash VestedExtendedKey)
-> IsString (Hash VestedExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash VestedExtendedKey
$cfromString :: String -> Hash VestedExtendedKey
IsString) via UsingRawBytesHex (Hash VestedExtendedKey)
deriving (Typeable (Hash VestedExtendedKey)
Typeable (Hash VestedExtendedKey)
-> (Hash VestedExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedExtendedKey] -> Size)
-> ToCBOR (Hash VestedExtendedKey)
Hash VestedExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedExtendedKey) -> Size
toCBOR :: Hash VestedExtendedKey -> Encoding
$ctoCBOR :: Hash VestedExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash VestedExtendedKey)
ToCBOR, Typeable (Hash VestedExtendedKey)
Decoder s (Hash VestedExtendedKey)
Typeable (Hash VestedExtendedKey)
-> (forall s. Decoder s (Hash VestedExtendedKey))
-> (Proxy (Hash VestedExtendedKey) -> Text)
-> FromCBOR (Hash VestedExtendedKey)
Proxy (Hash VestedExtendedKey) -> Text
forall s. Decoder s (Hash VestedExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash VestedExtendedKey) -> Text
$clabel :: Proxy (Hash VestedExtendedKey) -> Text
fromCBOR :: Decoder s (Hash VestedExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash VestedExtendedKey)
$cp1FromCBOR :: Typeable (Hash VestedExtendedKey)
FromCBOR) via UsingRawBytes (Hash VestedExtendedKey)
deriving anyclass HasTypeProxy (Hash VestedExtendedKey)
HasTypeProxy (Hash VestedExtendedKey)
-> (Hash VestedExtendedKey -> ByteString)
-> (AsType (Hash VestedExtendedKey)
-> ByteString -> Either DecoderError (Hash VestedExtendedKey))
-> SerialiseAsCBOR (Hash VestedExtendedKey)
AsType (Hash VestedExtendedKey)
-> ByteString -> Either DecoderError (Hash VestedExtendedKey)
Hash VestedExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash VestedExtendedKey)
-> ByteString -> Either DecoderError (Hash VestedExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash VestedExtendedKey)
-> ByteString -> Either DecoderError (Hash VestedExtendedKey)
serialiseToCBOR :: Hash VestedExtendedKey -> ByteString
$cserialiseToCBOR :: Hash VestedExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash VestedExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash VestedExtendedKey) where
serialiseToRawBytes :: Hash VestedExtendedKey -> ByteString
serialiseToRawBytes (VestedExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash VestedExtendedKey)
-> ByteString -> Maybe (Hash VestedExtendedKey)
deserialiseFromRawBytes (AsHash AsVestedExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash VestedExtendedKey
VestedExtendedKeyHash (KeyHash 'Staking StandardCrypto -> Hash VestedExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash VestedExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey VestedExtendedKey) where
textEnvelopeType :: AsType (VerificationKey VestedExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey VestedExtendedKey)
_ = TextEnvelopeType
"VestedExtendedVerificationKey_ed25519_bip32"
instance HasTextEnvelope (SigningKey VestedExtendedKey) where
textEnvelopeType :: AsType (SigningKey VestedExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey VestedExtendedKey)
_ = TextEnvelopeType
"VestedExtendedSigningKey_ed25519_bip32"
instance CastVerificationKeyRole VestedExtendedKey VestedKey where
castVerificationKey :: VerificationKey VestedExtendedKey -> VerificationKey VestedKey
castVerificationKey (VestedExtendedVerificationKey vk) =
VKey 'Vested StandardCrypto -> VerificationKey VestedKey
VestedVerificationKey
(VKey 'Vested StandardCrypto -> VerificationKey VestedKey)
-> (XPub -> VKey 'Vested StandardCrypto)
-> XPub
-> VerificationKey VestedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'Vested StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'Vested StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'Vested StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey VestedKey)
-> XPub -> VerificationKey VestedKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data VestedDelegateKey
instance HasTypeProxy VestedDelegateKey where
data AsType VestedDelegateKey = AsVestedDelegateKey
proxyToAsType :: Proxy VestedDelegateKey -> AsType VestedDelegateKey
proxyToAsType Proxy VestedDelegateKey
_ = AsType VestedDelegateKey
AsVestedDelegateKey
instance Key VestedDelegateKey where
newtype VerificationKey VestedDelegateKey =
VestedDelegateVerificationKey (Sophie.VKey Sophie.VestedDelegate StandardCrypto)
deriving stock (VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool
(VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool)
-> (VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool)
-> Eq (VerificationKey VestedDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool
$c/= :: VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool
== :: VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool
$c== :: VerificationKey VestedDelegateKey
-> VerificationKey VestedDelegateKey -> Bool
Eq)
deriving (Int -> VerificationKey VestedDelegateKey -> ShowS
[VerificationKey VestedDelegateKey] -> ShowS
VerificationKey VestedDelegateKey -> String
(Int -> VerificationKey VestedDelegateKey -> ShowS)
-> (VerificationKey VestedDelegateKey -> String)
-> ([VerificationKey VestedDelegateKey] -> ShowS)
-> Show (VerificationKey VestedDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey VestedDelegateKey] -> ShowS
$cshowList :: [VerificationKey VestedDelegateKey] -> ShowS
show :: VerificationKey VestedDelegateKey -> String
$cshow :: VerificationKey VestedDelegateKey -> String
showsPrec :: Int -> VerificationKey VestedDelegateKey -> ShowS
$cshowsPrec :: Int -> VerificationKey VestedDelegateKey -> ShowS
Show, String -> VerificationKey VestedDelegateKey
(String -> VerificationKey VestedDelegateKey)
-> IsString (VerificationKey VestedDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey VestedDelegateKey
$cfromString :: String -> VerificationKey VestedDelegateKey
IsString) via UsingRawBytesHex (VerificationKey VestedDelegateKey)
deriving newtype (Typeable (VerificationKey VestedDelegateKey)
Typeable (VerificationKey VestedDelegateKey)
-> (VerificationKey VestedDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedDelegateKey] -> Size)
-> ToCBOR (VerificationKey VestedDelegateKey)
VerificationKey VestedDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey VestedDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey VestedDelegateKey) -> Size
toCBOR :: VerificationKey VestedDelegateKey -> Encoding
$ctoCBOR :: VerificationKey VestedDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey VestedDelegateKey)
ToCBOR, Typeable (VerificationKey VestedDelegateKey)
Decoder s (VerificationKey VestedDelegateKey)
Typeable (VerificationKey VestedDelegateKey)
-> (forall s. Decoder s (VerificationKey VestedDelegateKey))
-> (Proxy (VerificationKey VestedDelegateKey) -> Text)
-> FromCBOR (VerificationKey VestedDelegateKey)
Proxy (VerificationKey VestedDelegateKey) -> Text
forall s. Decoder s (VerificationKey VestedDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey VestedDelegateKey) -> Text
$clabel :: Proxy (VerificationKey VestedDelegateKey) -> Text
fromCBOR :: Decoder s (VerificationKey VestedDelegateKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey VestedDelegateKey)
$cp1FromCBOR :: Typeable (VerificationKey VestedDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey VestedDelegateKey)
HasTypeProxy (VerificationKey VestedDelegateKey)
-> (VerificationKey VestedDelegateKey -> ByteString)
-> (AsType (VerificationKey VestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateKey))
-> SerialiseAsCBOR (VerificationKey VestedDelegateKey)
AsType (VerificationKey VestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateKey)
VerificationKey VestedDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey VestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey VestedDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateKey)
serialiseToCBOR :: VerificationKey VestedDelegateKey -> ByteString
$cserialiseToCBOR :: VerificationKey VestedDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey VestedDelegateKey)
SerialiseAsCBOR
newtype SigningKey VestedDelegateKey =
VestedDelegateSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey VestedDelegateKey -> ShowS
[SigningKey VestedDelegateKey] -> ShowS
SigningKey VestedDelegateKey -> String
(Int -> SigningKey VestedDelegateKey -> ShowS)
-> (SigningKey VestedDelegateKey -> String)
-> ([SigningKey VestedDelegateKey] -> ShowS)
-> Show (SigningKey VestedDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey VestedDelegateKey] -> ShowS
$cshowList :: [SigningKey VestedDelegateKey] -> ShowS
show :: SigningKey VestedDelegateKey -> String
$cshow :: SigningKey VestedDelegateKey -> String
showsPrec :: Int -> SigningKey VestedDelegateKey -> ShowS
$cshowsPrec :: Int -> SigningKey VestedDelegateKey -> ShowS
Show, String -> SigningKey VestedDelegateKey
(String -> SigningKey VestedDelegateKey)
-> IsString (SigningKey VestedDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey VestedDelegateKey
$cfromString :: String -> SigningKey VestedDelegateKey
IsString) via UsingRawBytesHex (SigningKey VestedDelegateKey)
deriving newtype (Typeable (SigningKey VestedDelegateKey)
Typeable (SigningKey VestedDelegateKey)
-> (SigningKey VestedDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedDelegateKey] -> Size)
-> ToCBOR (SigningKey VestedDelegateKey)
SigningKey VestedDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey VestedDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey VestedDelegateKey) -> Size
toCBOR :: SigningKey VestedDelegateKey -> Encoding
$ctoCBOR :: SigningKey VestedDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey VestedDelegateKey)
ToCBOR, Typeable (SigningKey VestedDelegateKey)
Decoder s (SigningKey VestedDelegateKey)
Typeable (SigningKey VestedDelegateKey)
-> (forall s. Decoder s (SigningKey VestedDelegateKey))
-> (Proxy (SigningKey VestedDelegateKey) -> Text)
-> FromCBOR (SigningKey VestedDelegateKey)
Proxy (SigningKey VestedDelegateKey) -> Text
forall s. Decoder s (SigningKey VestedDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey VestedDelegateKey) -> Text
$clabel :: Proxy (SigningKey VestedDelegateKey) -> Text
fromCBOR :: Decoder s (SigningKey VestedDelegateKey)
$cfromCBOR :: forall s. Decoder s (SigningKey VestedDelegateKey)
$cp1FromCBOR :: Typeable (SigningKey VestedDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey VestedDelegateKey)
HasTypeProxy (SigningKey VestedDelegateKey)
-> (SigningKey VestedDelegateKey -> ByteString)
-> (AsType (SigningKey VestedDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey VestedDelegateKey))
-> SerialiseAsCBOR (SigningKey VestedDelegateKey)
AsType (SigningKey VestedDelegateKey)
-> ByteString -> Either DecoderError (SigningKey VestedDelegateKey)
SigningKey VestedDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey VestedDelegateKey)
-> ByteString -> Either DecoderError (SigningKey VestedDelegateKey)
$cdeserialiseFromCBOR :: AsType (SigningKey VestedDelegateKey)
-> ByteString -> Either DecoderError (SigningKey VestedDelegateKey)
serialiseToCBOR :: SigningKey VestedDelegateKey -> ByteString
$cserialiseToCBOR :: SigningKey VestedDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey VestedDelegateKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType VestedDelegateKey -> Crypto.Seed -> SigningKey VestedDelegateKey
deterministicSigningKey :: AsType VestedDelegateKey -> Seed -> SigningKey VestedDelegateKey
deterministicSigningKey AsType VestedDelegateKey
AsVestedDelegateKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey VestedDelegateKey
VestedDelegateSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType VestedDelegateKey -> Word
deterministicSigningKeySeedSize :: AsType VestedDelegateKey -> Word
deterministicSigningKeySeedSize AsType VestedDelegateKey
AsVestedDelegateKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey VestedDelegateKey -> VerificationKey VestedDelegateKey
getVerificationKey :: SigningKey VestedDelegateKey -> VerificationKey VestedDelegateKey
getVerificationKey (VestedDelegateSigningKey sk) =
VKey 'VestedDelegate StandardCrypto
-> VerificationKey VestedDelegateKey
VestedDelegateVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'VestedDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey VestedDelegateKey -> Hash VestedDelegateKey
verificationKeyHash :: VerificationKey VestedDelegateKey -> Hash VestedDelegateKey
verificationKeyHash (VestedDelegateVerificationKey vkey) =
KeyHash 'VestedDelegate StandardCrypto -> Hash VestedDelegateKey
VestedDelegateKeyHash (VKey 'VestedDelegate StandardCrypto
-> KeyHash 'VestedDelegate StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'VestedDelegate StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey VestedDelegateKey) where
serialiseToRawBytes :: VerificationKey VestedDelegateKey -> ByteString
serialiseToRawBytes (VestedDelegateVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey VestedDelegateKey)
-> ByteString -> Maybe (VerificationKey VestedDelegateKey)
deserialiseFromRawBytes (AsVerificationKey AsVestedDelegateKey) ByteString
bs =
VKey 'VestedDelegate StandardCrypto
-> VerificationKey VestedDelegateKey
VestedDelegateVerificationKey (VKey 'VestedDelegate StandardCrypto
-> VerificationKey VestedDelegateKey)
-> (VerKeyDSIGN Ed25519DSIGN
-> VKey 'VestedDelegate StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey VestedDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'VestedDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey VestedDelegateKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey VestedDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey VestedDelegateKey) where
serialiseToRawBytes :: SigningKey VestedDelegateKey -> ByteString
serialiseToRawBytes (VestedDelegateSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey VestedDelegateKey)
-> ByteString -> Maybe (SigningKey VestedDelegateKey)
deserialiseFromRawBytes (AsSigningKey AsVestedDelegateKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey VestedDelegateKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey VestedDelegateKey
VestedDelegateSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey VestedDelegateKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey VestedDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash VestedDelegateKey =
VestedDelegateKeyHash (Sophie.KeyHash Sophie.VestedDelegate StandardCrypto)
deriving stock (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
(Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool)
-> (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool)
-> Eq (Hash VestedDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
$c/= :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
== :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
$c== :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
Eq, Eq (Hash VestedDelegateKey)
Eq (Hash VestedDelegateKey)
-> (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Ordering)
-> (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool)
-> (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool)
-> (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool)
-> (Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool)
-> (Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey)
-> (Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey)
-> Ord (Hash VestedDelegateKey)
Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
Hash VestedDelegateKey -> Hash VestedDelegateKey -> Ordering
Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey
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
min :: Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey
$cmin :: Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey
max :: Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey
$cmax :: Hash VestedDelegateKey
-> Hash VestedDelegateKey -> Hash VestedDelegateKey
>= :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
$c>= :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
> :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
$c> :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
<= :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
$c<= :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
< :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
$c< :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Bool
compare :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Ordering
$ccompare :: Hash VestedDelegateKey -> Hash VestedDelegateKey -> Ordering
$cp1Ord :: Eq (Hash VestedDelegateKey)
Ord)
deriving (Int -> Hash VestedDelegateKey -> ShowS
[Hash VestedDelegateKey] -> ShowS
Hash VestedDelegateKey -> String
(Int -> Hash VestedDelegateKey -> ShowS)
-> (Hash VestedDelegateKey -> String)
-> ([Hash VestedDelegateKey] -> ShowS)
-> Show (Hash VestedDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash VestedDelegateKey] -> ShowS
$cshowList :: [Hash VestedDelegateKey] -> ShowS
show :: Hash VestedDelegateKey -> String
$cshow :: Hash VestedDelegateKey -> String
showsPrec :: Int -> Hash VestedDelegateKey -> ShowS
$cshowsPrec :: Int -> Hash VestedDelegateKey -> ShowS
Show, String -> Hash VestedDelegateKey
(String -> Hash VestedDelegateKey)
-> IsString (Hash VestedDelegateKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash VestedDelegateKey
$cfromString :: String -> Hash VestedDelegateKey
IsString) via UsingRawBytesHex (Hash VestedDelegateKey)
deriving (Typeable (Hash VestedDelegateKey)
Typeable (Hash VestedDelegateKey)
-> (Hash VestedDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateKey] -> Size)
-> ToCBOR (Hash VestedDelegateKey)
Hash VestedDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateKey) -> Size
toCBOR :: Hash VestedDelegateKey -> Encoding
$ctoCBOR :: Hash VestedDelegateKey -> Encoding
$cp1ToCBOR :: Typeable (Hash VestedDelegateKey)
ToCBOR, Typeable (Hash VestedDelegateKey)
Decoder s (Hash VestedDelegateKey)
Typeable (Hash VestedDelegateKey)
-> (forall s. Decoder s (Hash VestedDelegateKey))
-> (Proxy (Hash VestedDelegateKey) -> Text)
-> FromCBOR (Hash VestedDelegateKey)
Proxy (Hash VestedDelegateKey) -> Text
forall s. Decoder s (Hash VestedDelegateKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash VestedDelegateKey) -> Text
$clabel :: Proxy (Hash VestedDelegateKey) -> Text
fromCBOR :: Decoder s (Hash VestedDelegateKey)
$cfromCBOR :: forall s. Decoder s (Hash VestedDelegateKey)
$cp1FromCBOR :: Typeable (Hash VestedDelegateKey)
FromCBOR) via UsingRawBytes (Hash VestedDelegateKey)
deriving anyclass HasTypeProxy (Hash VestedDelegateKey)
HasTypeProxy (Hash VestedDelegateKey)
-> (Hash VestedDelegateKey -> ByteString)
-> (AsType (Hash VestedDelegateKey)
-> ByteString -> Either DecoderError (Hash VestedDelegateKey))
-> SerialiseAsCBOR (Hash VestedDelegateKey)
AsType (Hash VestedDelegateKey)
-> ByteString -> Either DecoderError (Hash VestedDelegateKey)
Hash VestedDelegateKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash VestedDelegateKey)
-> ByteString -> Either DecoderError (Hash VestedDelegateKey)
$cdeserialiseFromCBOR :: AsType (Hash VestedDelegateKey)
-> ByteString -> Either DecoderError (Hash VestedDelegateKey)
serialiseToCBOR :: Hash VestedDelegateKey -> ByteString
$cserialiseToCBOR :: Hash VestedDelegateKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash VestedDelegateKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash VestedDelegateKey) where
serialiseToRawBytes :: Hash VestedDelegateKey -> ByteString
serialiseToRawBytes (VestedDelegateKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash VestedDelegateKey)
-> ByteString -> Maybe (Hash VestedDelegateKey)
deserialiseFromRawBytes (AsHash AsVestedDelegateKey) ByteString
bs =
KeyHash 'VestedDelegate StandardCrypto -> Hash VestedDelegateKey
VestedDelegateKeyHash (KeyHash 'VestedDelegate StandardCrypto -> Hash VestedDelegateKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'VestedDelegate StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'VestedDelegate StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedDelegateKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash VestedDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey VestedDelegateKey) where
textEnvelopeType :: AsType (VerificationKey VestedDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey VestedDelegateKey)
_ = TextEnvelopeType
"VestedDelegateVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey VestedDelegateKey) where
textEnvelopeType :: AsType (SigningKey VestedDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey VestedDelegateKey)
_ = TextEnvelopeType
"VestedDelegateSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole VestedDelegateKey StakePoolKey where
castVerificationKey :: VerificationKey VestedDelegateKey -> VerificationKey StakePoolKey
castVerificationKey (VestedDelegateVerificationKey (Sophie.VKey vkey)) =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'StakePool StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole VestedDelegateKey StakePoolKey where
castSigningKey :: SigningKey VestedDelegateKey -> SigningKey StakePoolKey
castSigningKey (VestedDelegateSigningKey skey) =
SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
StakePoolSigningKey SignKeyDSIGN StandardCrypto
skey
data VestedDelegateExtendedKey
instance HasTypeProxy VestedDelegateExtendedKey where
data AsType VestedDelegateExtendedKey = AsVestedDelegateExtendedKey
proxyToAsType :: Proxy VestedDelegateExtendedKey -> AsType VestedDelegateExtendedKey
proxyToAsType Proxy VestedDelegateExtendedKey
_ = AsType VestedDelegateExtendedKey
AsVestedDelegateExtendedKey
instance Key VestedDelegateExtendedKey where
newtype VerificationKey VestedDelegateExtendedKey =
VestedDelegateExtendedVerificationKey Crypto.HD.XPub
deriving stock (VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool
(VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool)
-> (VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool)
-> Eq (VerificationKey VestedDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool
$c/= :: VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool
== :: VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool
$c== :: VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey -> Bool
Eq)
deriving anyclass HasTypeProxy (VerificationKey VestedDelegateExtendedKey)
HasTypeProxy (VerificationKey VestedDelegateExtendedKey)
-> (VerificationKey VestedDelegateExtendedKey -> ByteString)
-> (AsType (VerificationKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateExtendedKey))
-> SerialiseAsCBOR (VerificationKey VestedDelegateExtendedKey)
AsType (VerificationKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateExtendedKey)
VerificationKey VestedDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey VestedDelegateExtendedKey)
serialiseToCBOR :: VerificationKey VestedDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: VerificationKey VestedDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey VestedDelegateExtendedKey)
SerialiseAsCBOR
deriving (Int -> VerificationKey VestedDelegateExtendedKey -> ShowS
[VerificationKey VestedDelegateExtendedKey] -> ShowS
VerificationKey VestedDelegateExtendedKey -> String
(Int -> VerificationKey VestedDelegateExtendedKey -> ShowS)
-> (VerificationKey VestedDelegateExtendedKey -> String)
-> ([VerificationKey VestedDelegateExtendedKey] -> ShowS)
-> Show (VerificationKey VestedDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey VestedDelegateExtendedKey] -> ShowS
$cshowList :: [VerificationKey VestedDelegateExtendedKey] -> ShowS
show :: VerificationKey VestedDelegateExtendedKey -> String
$cshow :: VerificationKey VestedDelegateExtendedKey -> String
showsPrec :: Int -> VerificationKey VestedDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> VerificationKey VestedDelegateExtendedKey -> ShowS
Show, String -> VerificationKey VestedDelegateExtendedKey
(String -> VerificationKey VestedDelegateExtendedKey)
-> IsString (VerificationKey VestedDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey VestedDelegateExtendedKey
$cfromString :: String -> VerificationKey VestedDelegateExtendedKey
IsString) via UsingRawBytesHex (VerificationKey VestedDelegateExtendedKey)
newtype SigningKey VestedDelegateExtendedKey =
VestedDelegateExtendedSigningKey Crypto.HD.XPrv
deriving anyclass HasTypeProxy (SigningKey VestedDelegateExtendedKey)
HasTypeProxy (SigningKey VestedDelegateExtendedKey)
-> (SigningKey VestedDelegateExtendedKey -> ByteString)
-> (AsType (SigningKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey VestedDelegateExtendedKey))
-> SerialiseAsCBOR (SigningKey VestedDelegateExtendedKey)
AsType (SigningKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey VestedDelegateExtendedKey)
SigningKey VestedDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey VestedDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (SigningKey VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey VestedDelegateExtendedKey)
serialiseToCBOR :: SigningKey VestedDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: SigningKey VestedDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey VestedDelegateExtendedKey)
SerialiseAsCBOR
deriving (Int -> SigningKey VestedDelegateExtendedKey -> ShowS
[SigningKey VestedDelegateExtendedKey] -> ShowS
SigningKey VestedDelegateExtendedKey -> String
(Int -> SigningKey VestedDelegateExtendedKey -> ShowS)
-> (SigningKey VestedDelegateExtendedKey -> String)
-> ([SigningKey VestedDelegateExtendedKey] -> ShowS)
-> Show (SigningKey VestedDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey VestedDelegateExtendedKey] -> ShowS
$cshowList :: [SigningKey VestedDelegateExtendedKey] -> ShowS
show :: SigningKey VestedDelegateExtendedKey -> String
$cshow :: SigningKey VestedDelegateExtendedKey -> String
showsPrec :: Int -> SigningKey VestedDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> SigningKey VestedDelegateExtendedKey -> ShowS
Show, String -> SigningKey VestedDelegateExtendedKey
(String -> SigningKey VestedDelegateExtendedKey)
-> IsString (SigningKey VestedDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey VestedDelegateExtendedKey
$cfromString :: String -> SigningKey VestedDelegateExtendedKey
IsString) via UsingRawBytesHex (SigningKey VestedDelegateExtendedKey)
deterministicSigningKey :: AsType VestedDelegateExtendedKey
-> Crypto.Seed
-> SigningKey VestedDelegateExtendedKey
deterministicSigningKey :: AsType VestedDelegateExtendedKey
-> Seed -> SigningKey VestedDelegateExtendedKey
deterministicSigningKey AsType VestedDelegateExtendedKey
AsVestedDelegateExtendedKey Seed
seed =
XPrv -> SigningKey VestedDelegateExtendedKey
VestedDelegateExtendedSigningKey
(ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
where
(ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed
deterministicSigningKeySeedSize :: AsType VestedDelegateExtendedKey -> Word
deterministicSigningKeySeedSize :: AsType VestedDelegateExtendedKey -> Word
deterministicSigningKeySeedSize AsType VestedDelegateExtendedKey
AsVestedDelegateExtendedKey = Word
32
getVerificationKey :: SigningKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey
getVerificationKey :: SigningKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateExtendedKey
getVerificationKey (VestedDelegateExtendedSigningKey sk) =
XPub -> VerificationKey VestedDelegateExtendedKey
VestedDelegateExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey
verificationKeyHash :: VerificationKey VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey
verificationKeyHash (VestedDelegateExtendedVerificationKey vk) =
KeyHash 'Staking StandardCrypto -> Hash VestedDelegateExtendedKey
VestedDelegateExtendedKeyHash
(KeyHash 'Staking StandardCrypto -> Hash VestedDelegateExtendedKey)
-> (Hash Blake2b_224 XPub -> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 XPub
-> Hash VestedDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash
(Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> (Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Hash Blake2b_224 XPub
-> KeyHash 'Staking StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 XPub
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
(Hash Blake2b_224 XPub -> Hash VestedDelegateExtendedKey)
-> Hash Blake2b_224 XPub -> Hash VestedDelegateExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash Blake2b_224 XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk
instance ToCBOR (VerificationKey VestedDelegateExtendedKey) where
toCBOR :: VerificationKey VestedDelegateExtendedKey -> Encoding
toCBOR (VestedDelegateExtendedVerificationKey xpub) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey VestedDelegateExtendedKey) where
fromCBOR :: Decoder s (VerificationKey VestedDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (VerificationKey VestedDelegateExtendedKey))
-> (XPub -> Decoder s (VerificationKey VestedDelegateExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey VestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (VerificationKey VestedDelegateExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (VerificationKey VestedDelegateExtendedKey
-> Decoder s (VerificationKey VestedDelegateExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey VestedDelegateExtendedKey
-> Decoder s (VerificationKey VestedDelegateExtendedKey))
-> (XPub -> VerificationKey VestedDelegateExtendedKey)
-> XPub
-> Decoder s (VerificationKey VestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey VestedDelegateExtendedKey
VestedDelegateExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))
instance ToCBOR (SigningKey VestedDelegateExtendedKey) where
toCBOR :: SigningKey VestedDelegateExtendedKey -> Encoding
toCBOR (VestedDelegateExtendedSigningKey xprv) =
ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey VestedDelegateExtendedKey) where
fromCBOR :: Decoder s (SigningKey VestedDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
(String -> Decoder s (SigningKey VestedDelegateExtendedKey))
-> (XPrv -> Decoder s (SigningKey VestedDelegateExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey VestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Decoder s (SigningKey VestedDelegateExtendedKey)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SigningKey VestedDelegateExtendedKey
-> Decoder s (SigningKey VestedDelegateExtendedKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey VestedDelegateExtendedKey
-> Decoder s (SigningKey VestedDelegateExtendedKey))
-> (XPrv -> SigningKey VestedDelegateExtendedKey)
-> XPrv
-> Decoder s (SigningKey VestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey VestedDelegateExtendedKey
VestedDelegateExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))
instance SerialiseAsRawBytes (VerificationKey VestedDelegateExtendedKey) where
serialiseToRawBytes :: VerificationKey VestedDelegateExtendedKey -> ByteString
serialiseToRawBytes (VestedDelegateExtendedVerificationKey xpub) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey VestedDelegateExtendedKey)
-> ByteString -> Maybe (VerificationKey VestedDelegateExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsVestedDelegateExtendedKey) ByteString
bs =
(String -> Maybe (VerificationKey VestedDelegateExtendedKey))
-> (XPub -> Maybe (VerificationKey VestedDelegateExtendedKey))
-> Either String XPub
-> Maybe (VerificationKey VestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey VestedDelegateExtendedKey)
-> String -> Maybe (VerificationKey VestedDelegateExtendedKey)
forall a b. a -> b -> a
const Maybe (VerificationKey VestedDelegateExtendedKey)
forall a. Maybe a
Nothing) (VerificationKey VestedDelegateExtendedKey
-> Maybe (VerificationKey VestedDelegateExtendedKey)
forall a. a -> Maybe a
Just (VerificationKey VestedDelegateExtendedKey
-> Maybe (VerificationKey VestedDelegateExtendedKey))
-> (XPub -> VerificationKey VestedDelegateExtendedKey)
-> XPub
-> Maybe (VerificationKey VestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey VestedDelegateExtendedKey
VestedDelegateExtendedVerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey VestedDelegateExtendedKey) where
serialiseToRawBytes :: SigningKey VestedDelegateExtendedKey -> ByteString
serialiseToRawBytes (VestedDelegateExtendedSigningKey xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey VestedDelegateExtendedKey)
-> ByteString -> Maybe (SigningKey VestedDelegateExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsVestedDelegateExtendedKey) ByteString
bs =
(String -> Maybe (SigningKey VestedDelegateExtendedKey))
-> (XPrv -> Maybe (SigningKey VestedDelegateExtendedKey))
-> Either String XPrv
-> Maybe (SigningKey VestedDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey VestedDelegateExtendedKey)
-> String -> Maybe (SigningKey VestedDelegateExtendedKey)
forall a b. a -> b -> a
const Maybe (SigningKey VestedDelegateExtendedKey)
forall a. Maybe a
Nothing) (SigningKey VestedDelegateExtendedKey
-> Maybe (SigningKey VestedDelegateExtendedKey)
forall a. a -> Maybe a
Just (SigningKey VestedDelegateExtendedKey
-> Maybe (SigningKey VestedDelegateExtendedKey))
-> (XPrv -> SigningKey VestedDelegateExtendedKey)
-> XPrv
-> Maybe (SigningKey VestedDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey VestedDelegateExtendedKey
VestedDelegateExtendedSigningKey)
(ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)
newtype instance Hash VestedDelegateExtendedKey =
VestedDelegateExtendedKeyHash (Sophie.KeyHash Sophie.Staking StandardCrypto)
deriving stock (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
(Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool)
-> Eq (Hash VestedDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
$c/= :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
== :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
$c== :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
Eq, Eq (Hash VestedDelegateExtendedKey)
Eq (Hash VestedDelegateExtendedKey)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Ordering)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey)
-> (Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey)
-> Ord (Hash VestedDelegateExtendedKey)
Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Ordering
Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Hash VestedDelegateExtendedKey
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
min :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Hash VestedDelegateExtendedKey
$cmin :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Hash VestedDelegateExtendedKey
max :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Hash VestedDelegateExtendedKey
$cmax :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Hash VestedDelegateExtendedKey
>= :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
$c>= :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
> :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
$c> :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
<= :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
$c<= :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
< :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
$c< :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Bool
compare :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Ordering
$ccompare :: Hash VestedDelegateExtendedKey
-> Hash VestedDelegateExtendedKey -> Ordering
$cp1Ord :: Eq (Hash VestedDelegateExtendedKey)
Ord)
deriving (Int -> Hash VestedDelegateExtendedKey -> ShowS
[Hash VestedDelegateExtendedKey] -> ShowS
Hash VestedDelegateExtendedKey -> String
(Int -> Hash VestedDelegateExtendedKey -> ShowS)
-> (Hash VestedDelegateExtendedKey -> String)
-> ([Hash VestedDelegateExtendedKey] -> ShowS)
-> Show (Hash VestedDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash VestedDelegateExtendedKey] -> ShowS
$cshowList :: [Hash VestedDelegateExtendedKey] -> ShowS
show :: Hash VestedDelegateExtendedKey -> String
$cshow :: Hash VestedDelegateExtendedKey -> String
showsPrec :: Int -> Hash VestedDelegateExtendedKey -> ShowS
$cshowsPrec :: Int -> Hash VestedDelegateExtendedKey -> ShowS
Show, String -> Hash VestedDelegateExtendedKey
(String -> Hash VestedDelegateExtendedKey)
-> IsString (Hash VestedDelegateExtendedKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash VestedDelegateExtendedKey
$cfromString :: String -> Hash VestedDelegateExtendedKey
IsString) via UsingRawBytesHex (Hash VestedDelegateExtendedKey)
deriving (Typeable (Hash VestedDelegateExtendedKey)
Typeable (Hash VestedDelegateExtendedKey)
-> (Hash VestedDelegateExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateExtendedKey] -> Size)
-> ToCBOR (Hash VestedDelegateExtendedKey)
Hash VestedDelegateExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateExtendedKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateExtendedKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash VestedDelegateExtendedKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateExtendedKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash VestedDelegateExtendedKey) -> Size
toCBOR :: Hash VestedDelegateExtendedKey -> Encoding
$ctoCBOR :: Hash VestedDelegateExtendedKey -> Encoding
$cp1ToCBOR :: Typeable (Hash VestedDelegateExtendedKey)
ToCBOR, Typeable (Hash VestedDelegateExtendedKey)
Decoder s (Hash VestedDelegateExtendedKey)
Typeable (Hash VestedDelegateExtendedKey)
-> (forall s. Decoder s (Hash VestedDelegateExtendedKey))
-> (Proxy (Hash VestedDelegateExtendedKey) -> Text)
-> FromCBOR (Hash VestedDelegateExtendedKey)
Proxy (Hash VestedDelegateExtendedKey) -> Text
forall s. Decoder s (Hash VestedDelegateExtendedKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash VestedDelegateExtendedKey) -> Text
$clabel :: Proxy (Hash VestedDelegateExtendedKey) -> Text
fromCBOR :: Decoder s (Hash VestedDelegateExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash VestedDelegateExtendedKey)
$cp1FromCBOR :: Typeable (Hash VestedDelegateExtendedKey)
FromCBOR) via UsingRawBytes (Hash VestedDelegateExtendedKey)
deriving anyclass HasTypeProxy (Hash VestedDelegateExtendedKey)
HasTypeProxy (Hash VestedDelegateExtendedKey)
-> (Hash VestedDelegateExtendedKey -> ByteString)
-> (AsType (Hash VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash VestedDelegateExtendedKey))
-> SerialiseAsCBOR (Hash VestedDelegateExtendedKey)
AsType (Hash VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash VestedDelegateExtendedKey)
Hash VestedDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash VestedDelegateExtendedKey)
$cdeserialiseFromCBOR :: AsType (Hash VestedDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash VestedDelegateExtendedKey)
serialiseToCBOR :: Hash VestedDelegateExtendedKey -> ByteString
$cserialiseToCBOR :: Hash VestedDelegateExtendedKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash VestedDelegateExtendedKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash VestedDelegateExtendedKey) where
serialiseToRawBytes :: Hash VestedDelegateExtendedKey -> ByteString
serialiseToRawBytes (VestedDelegateExtendedKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash VestedDelegateExtendedKey)
-> ByteString -> Maybe (Hash VestedDelegateExtendedKey)
deserialiseFromRawBytes (AsHash AsVestedDelegateExtendedKey) ByteString
bs =
KeyHash 'Staking StandardCrypto -> Hash VestedDelegateExtendedKey
VestedDelegateExtendedKeyHash (KeyHash 'Staking StandardCrypto -> Hash VestedDelegateExtendedKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'Staking StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash VestedDelegateExtendedKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash VestedDelegateExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance HasTextEnvelope (VerificationKey VestedDelegateExtendedKey) where
textEnvelopeType :: AsType (VerificationKey VestedDelegateExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey VestedDelegateExtendedKey)
_ = TextEnvelopeType
"VestedDelegateExtendedVerificationKey_ed25519_bip32"
instance HasTextEnvelope (SigningKey VestedDelegateExtendedKey) where
textEnvelopeType :: AsType (SigningKey VestedDelegateExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey VestedDelegateExtendedKey)
_ = TextEnvelopeType
"VestedDelegateExtendedSigningKey_ed25519_bip32"
instance CastVerificationKeyRole VestedDelegateExtendedKey VestedDelegateKey where
castVerificationKey :: VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateKey
castVerificationKey (VestedDelegateExtendedVerificationKey vk) =
VKey 'VestedDelegate StandardCrypto
-> VerificationKey VestedDelegateKey
VestedDelegateVerificationKey
(VKey 'VestedDelegate StandardCrypto
-> VerificationKey VestedDelegateKey)
-> (XPub -> VKey 'VestedDelegate StandardCrypto)
-> XPub
-> VerificationKey VestedDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'VestedDelegate StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey
(VerKeyDSIGN Ed25519DSIGN -> VKey 'VestedDelegate StandardCrypto)
-> (XPub -> VerKeyDSIGN Ed25519DSIGN)
-> XPub
-> VKey 'VestedDelegate StandardCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN Ed25519DSIGN
forall a. a
impossible
(Maybe (VerKeyDSIGN Ed25519DSIGN) -> VerKeyDSIGN Ed25519DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> XPub
-> VerKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
(ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
(XPub -> VerificationKey VestedDelegateKey)
-> XPub -> VerificationKey VestedDelegateKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: cole and sophie key sizes do not match!"
data StakePoolKey
instance HasTypeProxy StakePoolKey where
data AsType StakePoolKey = AsStakePoolKey
proxyToAsType :: Proxy StakePoolKey -> AsType StakePoolKey
proxyToAsType Proxy StakePoolKey
_ = AsType StakePoolKey
AsStakePoolKey
instance Key StakePoolKey where
newtype VerificationKey StakePoolKey =
StakePoolVerificationKey (Sophie.VKey Sophie.StakePool StandardCrypto)
deriving stock (VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
(VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool)
-> (VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool)
-> Eq (VerificationKey StakePoolKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
$c/= :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
== :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
$c== :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
Eq)
deriving (Int -> VerificationKey StakePoolKey -> ShowS
[VerificationKey StakePoolKey] -> ShowS
VerificationKey StakePoolKey -> String
(Int -> VerificationKey StakePoolKey -> ShowS)
-> (VerificationKey StakePoolKey -> String)
-> ([VerificationKey StakePoolKey] -> ShowS)
-> Show (VerificationKey StakePoolKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey StakePoolKey] -> ShowS
$cshowList :: [VerificationKey StakePoolKey] -> ShowS
show :: VerificationKey StakePoolKey -> String
$cshow :: VerificationKey StakePoolKey -> String
showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS
$cshowsPrec :: Int -> VerificationKey StakePoolKey -> ShowS
Show, String -> VerificationKey StakePoolKey
(String -> VerificationKey StakePoolKey)
-> IsString (VerificationKey StakePoolKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey StakePoolKey
$cfromString :: String -> VerificationKey StakePoolKey
IsString) via UsingRawBytesHex (VerificationKey StakePoolKey)
deriving newtype (Typeable (VerificationKey StakePoolKey)
Typeable (VerificationKey StakePoolKey)
-> (VerificationKey StakePoolKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size)
-> ToCBOR (VerificationKey StakePoolKey)
VerificationKey StakePoolKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size
toCBOR :: VerificationKey StakePoolKey -> Encoding
$ctoCBOR :: VerificationKey StakePoolKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey StakePoolKey)
ToCBOR, Typeable (VerificationKey StakePoolKey)
Decoder s (VerificationKey StakePoolKey)
Typeable (VerificationKey StakePoolKey)
-> (forall s. Decoder s (VerificationKey StakePoolKey))
-> (Proxy (VerificationKey StakePoolKey) -> Text)
-> FromCBOR (VerificationKey StakePoolKey)
Proxy (VerificationKey StakePoolKey) -> Text
forall s. Decoder s (VerificationKey StakePoolKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey StakePoolKey) -> Text
$clabel :: Proxy (VerificationKey StakePoolKey) -> Text
fromCBOR :: Decoder s (VerificationKey StakePoolKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey StakePoolKey)
$cp1FromCBOR :: Typeable (VerificationKey StakePoolKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey StakePoolKey)
HasTypeProxy (VerificationKey StakePoolKey)
-> (VerificationKey StakePoolKey -> ByteString)
-> (AsType (VerificationKey StakePoolKey)
-> ByteString
-> Either DecoderError (VerificationKey StakePoolKey))
-> SerialiseAsCBOR (VerificationKey StakePoolKey)
AsType (VerificationKey StakePoolKey)
-> ByteString -> Either DecoderError (VerificationKey StakePoolKey)
VerificationKey StakePoolKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey StakePoolKey)
-> ByteString -> Either DecoderError (VerificationKey StakePoolKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey StakePoolKey)
-> ByteString -> Either DecoderError (VerificationKey StakePoolKey)
serialiseToCBOR :: VerificationKey StakePoolKey -> ByteString
$cserialiseToCBOR :: VerificationKey StakePoolKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey StakePoolKey)
SerialiseAsCBOR
newtype SigningKey StakePoolKey =
StakePoolSigningKey (Sophie.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey StakePoolKey -> ShowS
[SigningKey StakePoolKey] -> ShowS
SigningKey StakePoolKey -> String
(Int -> SigningKey StakePoolKey -> ShowS)
-> (SigningKey StakePoolKey -> String)
-> ([SigningKey StakePoolKey] -> ShowS)
-> Show (SigningKey StakePoolKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey StakePoolKey] -> ShowS
$cshowList :: [SigningKey StakePoolKey] -> ShowS
show :: SigningKey StakePoolKey -> String
$cshow :: SigningKey StakePoolKey -> String
showsPrec :: Int -> SigningKey StakePoolKey -> ShowS
$cshowsPrec :: Int -> SigningKey StakePoolKey -> ShowS
Show, String -> SigningKey StakePoolKey
(String -> SigningKey StakePoolKey)
-> IsString (SigningKey StakePoolKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey StakePoolKey
$cfromString :: String -> SigningKey StakePoolKey
IsString) via UsingRawBytesHex (SigningKey StakePoolKey)
deriving newtype (Typeable (SigningKey StakePoolKey)
Typeable (SigningKey StakePoolKey)
-> (SigningKey StakePoolKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size)
-> ToCBOR (SigningKey StakePoolKey)
SigningKey StakePoolKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size
toCBOR :: SigningKey StakePoolKey -> Encoding
$ctoCBOR :: SigningKey StakePoolKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey StakePoolKey)
ToCBOR, Typeable (SigningKey StakePoolKey)
Decoder s (SigningKey StakePoolKey)
Typeable (SigningKey StakePoolKey)
-> (forall s. Decoder s (SigningKey StakePoolKey))
-> (Proxy (SigningKey StakePoolKey) -> Text)
-> FromCBOR (SigningKey StakePoolKey)
Proxy (SigningKey StakePoolKey) -> Text
forall s. Decoder s (SigningKey StakePoolKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey StakePoolKey) -> Text
$clabel :: Proxy (SigningKey StakePoolKey) -> Text
fromCBOR :: Decoder s (SigningKey StakePoolKey)
$cfromCBOR :: forall s. Decoder s (SigningKey StakePoolKey)
$cp1FromCBOR :: Typeable (SigningKey StakePoolKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey StakePoolKey)
HasTypeProxy (SigningKey StakePoolKey)
-> (SigningKey StakePoolKey -> ByteString)
-> (AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey))
-> SerialiseAsCBOR (SigningKey StakePoolKey)
AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey)
SigningKey StakePoolKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey)
$cdeserialiseFromCBOR :: AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey)
serialiseToCBOR :: SigningKey StakePoolKey -> ByteString
$cserialiseToCBOR :: SigningKey StakePoolKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey StakePoolKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType StakePoolKey -> Crypto.Seed -> SigningKey StakePoolKey
deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey
deterministicSigningKey AsType StakePoolKey
AsStakePoolKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
StakePoolSigningKey (Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word
deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word
deterministicSigningKeySeedSize AsType StakePoolKey
AsStakePoolKey =
Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey
getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey
getVerificationKey (StakePoolSigningKey sk) =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (VerKeyDSIGN (DSIGN StandardCrypto)
-> VKey 'StakePool StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk))
verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey
verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey
verificationKeyHash (StakePoolVerificationKey vkey) =
KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash (VKey 'StakePool StandardCrypto -> KeyHash 'StakePool StandardCrypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Sophie.hashKey VKey 'StakePool StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey StakePoolKey) where
serialiseToRawBytes :: VerificationKey StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolVerificationKey (Sophie.VKey vk)) =
VerKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
vk
deserialiseFromRawBytes :: AsType (VerificationKey StakePoolKey)
-> ByteString -> Maybe (VerificationKey StakePoolKey)
deserialiseFromRawBytes (AsVerificationKey AsStakePoolKey) ByteString
bs =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey)
-> (VerKeyDSIGN Ed25519DSIGN -> VKey 'StakePool StandardCrypto)
-> VerKeyDSIGN Ed25519DSIGN
-> VerificationKey StakePoolKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN Ed25519DSIGN -> VKey 'StakePool StandardCrypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey (VerKeyDSIGN Ed25519DSIGN -> VerificationKey StakePoolKey)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerificationKey StakePoolKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey StakePoolKey) where
serialiseToRawBytes :: SigningKey StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolSigningKey sk) =
SignKeyDSIGN Ed25519DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
SignKeyDSIGN Ed25519DSIGN
sk
deserialiseFromRawBytes :: AsType (SigningKey StakePoolKey)
-> ByteString -> Maybe (SigningKey StakePoolKey)
deserialiseFromRawBytes (AsSigningKey AsStakePoolKey) ByteString
bs =
SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
SignKeyDSIGN Ed25519DSIGN -> SigningKey StakePoolKey
StakePoolSigningKey (SignKeyDSIGN Ed25519DSIGN -> SigningKey StakePoolKey)
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
-> Maybe (SigningKey StakePoolKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
instance SerialiseAsBech32 (VerificationKey StakePoolKey) where
bech32PrefixFor :: VerificationKey StakePoolKey -> Text
bech32PrefixFor VerificationKey StakePoolKey
_ = Text
"pool_vk"
bech32PrefixesPermitted :: AsType (VerificationKey StakePoolKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey StakePoolKey)
_ = [Text
"pool_vk"]
instance SerialiseAsBech32 (SigningKey StakePoolKey) where
bech32PrefixFor :: SigningKey StakePoolKey -> Text
bech32PrefixFor SigningKey StakePoolKey
_ = Text
"pool_sk"
bech32PrefixesPermitted :: AsType (SigningKey StakePoolKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey StakePoolKey)
_ = [Text
"pool_sk"]
newtype instance Hash StakePoolKey =
StakePoolKeyHash (Sophie.KeyHash Sophie.StakePool StandardCrypto)
deriving stock (Hash StakePoolKey -> Hash StakePoolKey -> Bool
(Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> Eq (Hash StakePoolKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c/= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
== :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c== :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
Eq, Eq (Hash StakePoolKey)
Eq (Hash StakePoolKey)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Ordering)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey)
-> Ord (Hash StakePoolKey)
Hash StakePoolKey -> Hash StakePoolKey -> Bool
Hash StakePoolKey -> Hash StakePoolKey -> Ordering
Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
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
min :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
$cmin :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
max :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
$cmax :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
>= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c>= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
> :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c> :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
<= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c<= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
< :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c< :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
compare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering
$ccompare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering
$cp1Ord :: Eq (Hash StakePoolKey)
Ord)
deriving (Int -> Hash StakePoolKey -> ShowS
[Hash StakePoolKey] -> ShowS
Hash StakePoolKey -> String
(Int -> Hash StakePoolKey -> ShowS)
-> (Hash StakePoolKey -> String)
-> ([Hash StakePoolKey] -> ShowS)
-> Show (Hash StakePoolKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash StakePoolKey] -> ShowS
$cshowList :: [Hash StakePoolKey] -> ShowS
show :: Hash StakePoolKey -> String
$cshow :: Hash StakePoolKey -> String
showsPrec :: Int -> Hash StakePoolKey -> ShowS
$cshowsPrec :: Int -> Hash StakePoolKey -> ShowS
Show, String -> Hash StakePoolKey
(String -> Hash StakePoolKey) -> IsString (Hash StakePoolKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash StakePoolKey
$cfromString :: String -> Hash StakePoolKey
IsString) via UsingRawBytesHex (Hash StakePoolKey)
deriving (Typeable (Hash StakePoolKey)
Typeable (Hash StakePoolKey)
-> (Hash StakePoolKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size)
-> ToCBOR (Hash StakePoolKey)
Hash StakePoolKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size
toCBOR :: Hash StakePoolKey -> Encoding
$ctoCBOR :: Hash StakePoolKey -> Encoding
$cp1ToCBOR :: Typeable (Hash StakePoolKey)
ToCBOR, Typeable (Hash StakePoolKey)
Decoder s (Hash StakePoolKey)
Typeable (Hash StakePoolKey)
-> (forall s. Decoder s (Hash StakePoolKey))
-> (Proxy (Hash StakePoolKey) -> Text)
-> FromCBOR (Hash StakePoolKey)
Proxy (Hash StakePoolKey) -> Text
forall s. Decoder s (Hash StakePoolKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash StakePoolKey) -> Text
$clabel :: Proxy (Hash StakePoolKey) -> Text
fromCBOR :: Decoder s (Hash StakePoolKey)
$cfromCBOR :: forall s. Decoder s (Hash StakePoolKey)
$cp1FromCBOR :: Typeable (Hash StakePoolKey)
FromCBOR) via UsingRawBytes (Hash StakePoolKey)
deriving anyclass HasTypeProxy (Hash StakePoolKey)
HasTypeProxy (Hash StakePoolKey)
-> (Hash StakePoolKey -> ByteString)
-> (AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey))
-> SerialiseAsCBOR (Hash StakePoolKey)
AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey)
Hash StakePoolKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey)
$cdeserialiseFromCBOR :: AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey)
serialiseToCBOR :: Hash StakePoolKey -> ByteString
$cserialiseToCBOR :: Hash StakePoolKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash StakePoolKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash StakePoolKey) where
serialiseToRawBytes :: Hash StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolKeyHash (Sophie.KeyHash vkh)) =
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
vkh
deserialiseFromRawBytes :: AsType (Hash StakePoolKey)
-> ByteString -> Maybe (Hash StakePoolKey)
deserialiseFromRawBytes (AsHash AsStakePoolKey) ByteString
bs =
KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash (KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey)
-> (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'StakePool StandardCrypto)
-> Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> Hash StakePoolKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN)
-> KeyHash 'StakePool StandardCrypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Sophie.KeyHash (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN) -> Hash StakePoolKey)
-> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
-> Maybe (Hash StakePoolKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash Blake2b_224 (VerKeyDSIGN Ed25519DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs
instance SerialiseAsBech32 (Hash StakePoolKey) where
bech32PrefixFor :: Hash StakePoolKey -> Text
bech32PrefixFor Hash StakePoolKey
_ = Text
"pool"
bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text]
bech32PrefixesPermitted AsType (Hash StakePoolKey)
_ = [Text
"pool"]
instance ToJSON (Hash StakePoolKey) where
toJSON :: Hash StakePoolKey -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (Hash StakePoolKey -> Text) -> Hash StakePoolKey -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash StakePoolKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32
instance ToJSONKey (Hash StakePoolKey) where
toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey)
toJSONKey = (Hash StakePoolKey -> Text)
-> ToJSONKeyFunction (Hash StakePoolKey)
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText Hash StakePoolKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32
instance HasTextEnvelope (VerificationKey StakePoolKey) where
textEnvelopeType :: AsType (VerificationKey StakePoolKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey StakePoolKey)
_ = TextEnvelopeType
"StakePoolVerificationKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey StakePoolKey) where
textEnvelopeType :: AsType (SigningKey StakePoolKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakePoolKey)
_ = TextEnvelopeType
"StakePoolSigningKey_"
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy Ed25519DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
Proxy Ed25519DSIGN
proxy)
where
proxy :: Proxy (Sophie.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = Proxy (DSIGN StandardCrypto)
forall k (t :: k). Proxy t
Proxy