{-# 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 Cardano.Api.Keys.Shelley (
PaymentKey,
PaymentExtendedKey,
StakeKey,
StakeExtendedKey,
StakePoolKey,
GenesisKey,
GenesisExtendedKey,
GenesisDelegateKey,
GenesisDelegateExtendedKey,
GenesisUTxOKey,
AsType(..),
VerificationKey(..),
SigningKey(..),
Hash(..),
) where
import Data.Aeson.Types (ToJSONKey (..), toJSONKeyText, withText)
import Data.Bifunctor (first)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Either.Combinators (maybeToRight)
import Data.Maybe
import Data.String (IsString (..))
import qualified Data.Text as Text
import qualified Cardano.Crypto.DSIGN.Class as Crypto
import qualified Cardano.Crypto.Hash.Class as Crypto
import qualified Cardano.Crypto.Seed as Crypto
import qualified Cardano.Crypto.Wallet as Crypto.HD
import qualified Cardano.Ledger.Crypto as Shelley (DSIGN)
import qualified Cardano.Ledger.Keys as Shelley
import Cardano.Ledger.Crypto (StandardCrypto)
import Cardano.Api.Error
import Cardano.Api.Hash
import Cardano.Api.HasTypeProxy
import Cardano.Api.Keys.Class
import Cardano.Api.SerialiseBech32
import Cardano.Api.SerialiseCBOR
import Cardano.Api.SerialiseJSON
import Cardano.Api.SerialiseRaw
import Cardano.Api.SerialiseTextEnvelope
import Cardano.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 (Shelley.VKey Shelley.Payment StandardCrypto)
deriving stock (VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
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
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
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey PaymentKey
$cfromString :: String -> VerificationKey PaymentKey
IsString) via UsingRawBytesHex (VerificationKey PaymentKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (VerificationKey PaymentKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey PaymentKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
newtype SigningKey PaymentKey =
PaymentSigningKey (Shelley.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey PaymentKey -> ShowS
[SigningKey PaymentKey] -> ShowS
SigningKey PaymentKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey PaymentKey
$cfromString :: String -> SigningKey PaymentKey
IsString) via UsingRawBytesHex (SigningKey PaymentKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (SigningKey PaymentKey)
$cfromCBOR :: forall s. Decoder s (SigningKey PaymentKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deterministicSigningKey :: AsType PaymentKey -> Crypto.Seed -> SigningKey PaymentKey
deterministicSigningKey :: AsType PaymentKey -> Seed -> SigningKey PaymentKey
deterministicSigningKey AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
PaymentSigningKey (forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType PaymentKey -> Word
deterministicSigningKeySeedSize :: AsType PaymentKey -> Word
deterministicSigningKeySeedSize AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey =
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
proxy
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey
getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey
getVerificationKey (PaymentSigningKey SignKeyDSIGN StandardCrypto
sk) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey (forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
sk))
verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey
verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey
verificationKeyHash (PaymentVerificationKey VKey 'Payment StandardCrypto
vkey) =
KeyHash 'Payment StandardCrypto -> Hash PaymentKey
PaymentKeyHash (forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Shelley.hashKey VKey 'Payment StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey PaymentKey) where
serialiseToRawBytes :: VerificationKey PaymentKey -> ByteString
serialiseToRawBytes (PaymentVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
vk
deserialiseFromRawBytes :: AsType (VerificationKey PaymentKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
deserialiseFromRawBytes (AsVerificationKey AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey) ByteString
bs =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey PaymentKey"))
(forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey)
(forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs)
instance SerialiseAsRawBytes (SigningKey PaymentKey) where
serialiseToRawBytes :: SigningKey PaymentKey -> ByteString
serialiseToRawBytes (PaymentSigningKey SignKeyDSIGN StandardCrypto
sk) =
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
sk
deserialiseFromRawBytes :: AsType (SigningKey PaymentKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey PaymentKey)
deserialiseFromRawBytes (AsSigningKey AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey) ByteString
bs =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to serialise AsSigningKey AsPaymentKey"))
(forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
PaymentSigningKey)
(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 (Shelley.KeyHash Shelley.Payment StandardCrypto)
deriving stock (Hash PaymentKey -> Hash PaymentKey -> Bool
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)
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
Ord)
deriving (Int -> Hash PaymentKey -> ShowS
[Hash PaymentKey] -> ShowS
Hash PaymentKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash PaymentKey
$cfromString :: String -> Hash PaymentKey
IsString) via UsingRawBytesHex (Hash PaymentKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash PaymentKey)
$cfromCBOR :: forall s. Decoder s (Hash PaymentKey)
FromCBOR) via UsingRawBytes (Hash PaymentKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash PaymentKey) where
serialiseToRawBytes :: Hash PaymentKey -> ByteString
serialiseToRawBytes (PaymentKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash PaymentKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash PaymentKey)
deserialiseFromRawBytes (AsHash AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight
(String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash PaymentKey")
(KeyHash 'Payment StandardCrypto -> Hash PaymentKey
PaymentKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
"PaymentVerificationKeyShelley_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey PaymentKey) where
textEnvelopeType :: AsType (SigningKey PaymentKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey PaymentKey)
_ = TextEnvelopeType
"PaymentSigningKeyShelley_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = 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
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)
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
SerialiseAsCBOR
deriving (Int -> VerificationKey PaymentExtendedKey -> ShowS
[VerificationKey PaymentExtendedKey] -> ShowS
VerificationKey PaymentExtendedKey -> String
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
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)
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
SerialiseAsCBOR
deriving (Int -> SigningKey PaymentExtendedKey -> ShowS
[SigningKey PaymentExtendedKey] -> ShowS
SigningKey PaymentExtendedKey -> String
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
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
R:AsTypePaymentExtendedKey
AsPaymentExtendedKey Seed
seed =
XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey
(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
R:AsTypePaymentExtendedKey
AsPaymentExtendedKey = Word
32
getVerificationKey :: SigningKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey
getVerificationKey :: SigningKey PaymentExtendedKey -> VerificationKey PaymentExtendedKey
getVerificationKey (PaymentExtendedSigningKey XPrv
sk) =
XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey (HasCallStack => XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey PaymentExtendedKey
-> Hash PaymentExtendedKey
verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey
verificationKeyHash (PaymentExtendedVerificationKey XPub
vk) =
KeyHash 'Payment StandardCrypto -> Hash PaymentExtendedKey
PaymentExtendedKeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a b. Hash h a -> Hash h b
Crypto.castHash
forall a b. (a -> b) -> a -> b
$ 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
xpub) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey PaymentExtendedKey) where
fromCBOR :: forall s. Decoder s (VerificationKey PaymentExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return 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
xprv) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey PaymentExtendedKey) where
fromCBOR :: forall s. Decoder s (SigningKey PaymentExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey)
(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) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either
SerialiseAsRawBytesError (VerificationKey PaymentExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType PaymentExtendedKey
R:AsTypePaymentExtendedKey
AsPaymentExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
(forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey PaymentExtendedKey"))
(XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey PaymentExtendedKey) where
serialiseToRawBytes :: SigningKey PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedSigningKey XPrv
xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey PaymentExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType PaymentExtendedKey
R:AsTypePaymentExtendedKey
AsPaymentExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
(forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey PaymentExtendedKey"))
(XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 (Shelley.KeyHash Shelley.Payment StandardCrypto)
deriving stock (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
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)
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
Ord)
deriving (Int -> Hash PaymentExtendedKey -> ShowS
[Hash PaymentExtendedKey] -> ShowS
Hash PaymentExtendedKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash PaymentExtendedKey
$cfromString :: String -> Hash PaymentExtendedKey
IsString) via UsingRawBytesHex (Hash PaymentExtendedKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash PaymentExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash PaymentExtendedKey)
FromCBOR) via UsingRawBytes (Hash PaymentExtendedKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash PaymentExtendedKey) where
serialiseToRawBytes :: Hash PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash PaymentExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash PaymentExtendedKey)
deserialiseFromRawBytes (AsHash AsType PaymentExtendedKey
R:AsTypePaymentExtendedKey
AsPaymentExtendedKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash PaymentExtendedKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'Payment StandardCrypto -> Hash PaymentExtendedKey
PaymentExtendedKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
"PaymentExtendedVerificationKeyShelley_ed25519_bip32"
instance HasTextEnvelope (SigningKey PaymentExtendedKey) where
textEnvelopeType :: AsType (SigningKey PaymentExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey PaymentExtendedKey)
_ = TextEnvelopeType
"PaymentExtendedSigningKeyShelley_ed25519_bip32"
instance CastVerificationKeyRole PaymentExtendedKey PaymentKey where
castVerificationKey :: VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey
castVerificationKey (PaymentExtendedVerificationKey XPub
vk) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall {a}. a
impossible
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley 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
{ VerificationKey StakeKey -> VKey 'Staking StandardCrypto
unStakeVerificationKey :: Shelley.VKey Shelley.Staking StandardCrypto
}
deriving stock (VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
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)
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
ToCBOR, Typeable (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 :: forall s. Decoder s (VerificationKey StakeKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey StakeKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deriving (Int -> VerificationKey StakeKey -> ShowS
[VerificationKey StakeKey] -> ShowS
VerificationKey StakeKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey StakeKey
$cfromString :: String -> VerificationKey StakeKey
IsString) via UsingRawBytesHex (VerificationKey StakeKey)
newtype SigningKey StakeKey =
StakeSigningKey (Shelley.SignKeyDSIGN StandardCrypto)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (SigningKey StakeKey)
$cfromCBOR :: forall s. Decoder s (SigningKey StakeKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deriving (Int -> SigningKey StakeKey -> ShowS
[SigningKey StakeKey] -> ShowS
SigningKey StakeKey -> String
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
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
R:AsTypeStakeKey
AsStakeKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey StakeKey
StakeSigningKey (forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType StakeKey -> Word
deterministicSigningKeySeedSize :: AsType StakeKey -> Word
deterministicSigningKeySeedSize AsType StakeKey
R:AsTypeStakeKey
AsStakeKey =
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
proxy
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey
getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey
getVerificationKey (StakeSigningKey SignKeyDSIGN StandardCrypto
sk) =
VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey (forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
sk))
verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey
verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey
verificationKeyHash (StakeVerificationKey VKey 'Staking StandardCrypto
vkey) =
KeyHash 'Staking StandardCrypto -> Hash StakeKey
StakeKeyHash (forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Shelley.hashKey VKey 'Staking StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey StakeKey) where
serialiseToRawBytes :: VerificationKey StakeKey -> ByteString
serialiseToRawBytes (StakeVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
vk
deserialiseFromRawBytes :: AsType (VerificationKey StakeKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey StakeKey)
deserialiseFromRawBytes (AsVerificationKey AsType StakeKey
R:AsTypeStakeKey
AsStakeKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey StakeKey") forall a b. (a -> b) -> a -> b
$
VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey StakeKey) where
serialiseToRawBytes :: SigningKey StakeKey -> ByteString
serialiseToRawBytes (StakeSigningKey SignKeyDSIGN StandardCrypto
sk) =
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
sk
deserialiseFromRawBytes :: AsType (SigningKey StakeKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey StakeKey)
deserialiseFromRawBytes (AsSigningKey AsType StakeKey
R:AsTypeStakeKey
AsStakeKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey StakeKey") forall a b. (a -> b) -> a -> b
$
SignKeyDSIGN StandardCrypto -> SigningKey StakeKey
StakeSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 (Shelley.KeyHash Shelley.Staking StandardCrypto)
deriving stock (Hash StakeKey -> Hash StakeKey -> Bool
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)
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
Ord)
deriving (Int -> Hash StakeKey -> ShowS
[Hash StakeKey] -> ShowS
Hash StakeKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash StakeKey
$cfromString :: String -> Hash StakeKey
IsString) via UsingRawBytesHex (Hash StakeKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash StakeKey)
$cfromCBOR :: forall s. Decoder s (Hash StakeKey)
FromCBOR) via UsingRawBytes (Hash StakeKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash StakeKey) where
serialiseToRawBytes :: Hash StakeKey -> ByteString
serialiseToRawBytes (StakeKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash StakeKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash StakeKey)
deserialiseFromRawBytes (AsHash AsType StakeKey
R:AsTypeStakeKey
AsStakeKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakeKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'Staking StandardCrypto -> Hash StakeKey
StakeKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
"StakeVerificationKeyShelley_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey StakeKey) where
textEnvelopeType :: AsType (SigningKey StakeKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakeKey)
_ = TextEnvelopeType
"StakeSigningKeyShelley_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = 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
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)
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
SerialiseAsCBOR
deriving (Int -> VerificationKey StakeExtendedKey -> ShowS
[VerificationKey StakeExtendedKey] -> ShowS
VerificationKey StakeExtendedKey -> String
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
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)
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
SerialiseAsCBOR
deriving (Int -> SigningKey StakeExtendedKey -> ShowS
[SigningKey StakeExtendedKey] -> ShowS
SigningKey StakeExtendedKey -> String
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
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
R:AsTypeStakeExtendedKey
AsStakeExtendedKey Seed
seed =
XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey
(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
R:AsTypeStakeExtendedKey
AsStakeExtendedKey = Word
32
getVerificationKey :: SigningKey StakeExtendedKey
-> VerificationKey StakeExtendedKey
getVerificationKey :: SigningKey StakeExtendedKey -> VerificationKey StakeExtendedKey
getVerificationKey (StakeExtendedSigningKey XPrv
sk) =
XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey (HasCallStack => XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey StakeExtendedKey
-> Hash StakeExtendedKey
verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey
verificationKeyHash (StakeExtendedVerificationKey XPub
vk) =
KeyHash 'Staking StandardCrypto -> Hash StakeExtendedKey
StakeExtendedKeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a b. Hash h a -> Hash h b
Crypto.castHash
forall a b. (a -> b) -> a -> b
$ 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
xpub) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey StakeExtendedKey) where
fromCBOR :: forall s. Decoder s (VerificationKey StakeExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return 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
xprv) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey StakeExtendedKey) where
fromCBOR :: forall s. Decoder s (SigningKey StakeExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey)
(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) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either
SerialiseAsRawBytesError (VerificationKey StakeExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType StakeExtendedKey
R:AsTypeStakeExtendedKey
AsStakeExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (\String
msg -> String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError (String
"Unable to deserialise VerificationKey StakeExtendedKey: " forall a. [a] -> [a] -> [a]
++ String
msg)) forall a b. (a -> b) -> a -> b
$
XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs
instance SerialiseAsRawBytes (SigningKey StakeExtendedKey) where
serialiseToRawBytes :: SigningKey StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedSigningKey XPrv
xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey StakeExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey StakeExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType StakeExtendedKey
R:AsTypeStakeExtendedKey
AsStakeExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (\String
msg -> String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError (String
"Unable to deserialise SigningKey StakeExtendedKey: " forall a. [a] -> [a] -> [a]
++ String
msg)) forall a b. (a -> b) -> a -> b
$
XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 (Shelley.KeyHash Shelley.Staking StandardCrypto)
deriving stock (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
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)
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
Ord)
deriving (Int -> Hash StakeExtendedKey -> ShowS
[Hash StakeExtendedKey] -> ShowS
Hash StakeExtendedKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash StakeExtendedKey
$cfromString :: String -> Hash StakeExtendedKey
IsString) via UsingRawBytesHex (Hash StakeExtendedKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash StakeExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash StakeExtendedKey)
FromCBOR) via UsingRawBytes (Hash StakeExtendedKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash StakeExtendedKey) where
serialiseToRawBytes :: Hash StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash StakeExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash StakeExtendedKey)
deserialiseFromRawBytes (AsHash AsType StakeExtendedKey
R:AsTypeStakeExtendedKey
AsStakeExtendedKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakeExtendedKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'Staking StandardCrypto -> Hash StakeExtendedKey
StakeExtendedKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
"StakeExtendedVerificationKeyShelley_ed25519_bip32"
instance HasTextEnvelope (SigningKey StakeExtendedKey) where
textEnvelopeType :: AsType (SigningKey StakeExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakeExtendedKey)
_ = TextEnvelopeType
"StakeExtendedSigningKeyShelley_ed25519_bip32"
instance CastVerificationKeyRole StakeExtendedKey StakeKey where
castVerificationKey :: VerificationKey StakeExtendedKey -> VerificationKey StakeKey
castVerificationKey (StakeExtendedVerificationKey XPub
vk) =
VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall {a}. a
impossible
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley 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 (Shelley.VKey Shelley.Genesis StandardCrypto)
deriving stock (VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
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
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
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisKey
$cfromString :: String -> VerificationKey GenesisKey
IsString) via UsingRawBytesHex (VerificationKey GenesisKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (VerificationKey GenesisKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
newtype SigningKey GenesisKey =
GenesisSigningKey (Shelley.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisKey -> ShowS
[SigningKey GenesisKey] -> ShowS
SigningKey GenesisKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisKey
$cfromString :: String -> SigningKey GenesisKey
IsString) via UsingRawBytesHex (SigningKey GenesisKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (SigningKey GenesisKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisKey -> Crypto.Seed -> SigningKey GenesisKey
deterministicSigningKey :: AsType GenesisKey -> Seed -> SigningKey GenesisKey
deterministicSigningKey AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisKey
GenesisSigningKey (forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisKey -> Word
deterministicSigningKeySeedSize AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey =
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
proxy
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey
getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey
getVerificationKey (GenesisSigningKey SignKeyDSIGN StandardCrypto
sk) =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey
GenesisVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey (forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
sk))
verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey
verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey
verificationKeyHash (GenesisVerificationKey VKey 'Genesis StandardCrypto
vkey) =
KeyHash 'Genesis StandardCrypto -> Hash GenesisKey
GenesisKeyHash (forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Shelley.hashKey VKey 'Genesis StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisKey) where
serialiseToRawBytes :: VerificationKey GenesisKey -> ByteString
serialiseToRawBytes (GenesisVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey GenesisKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisKey") forall a b. (a -> b) -> a -> b
$
VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey
GenesisVerificationKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisKey) where
serialiseToRawBytes :: SigningKey GenesisKey -> ByteString
serialiseToRawBytes (GenesisSigningKey SignKeyDSIGN StandardCrypto
sk) =
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey GenesisKey") forall a b. (a -> b) -> a -> b
$
SignKeyDSIGN StandardCrypto -> SigningKey GenesisKey
GenesisSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisKey =
GenesisKeyHash (Shelley.KeyHash Shelley.Genesis StandardCrypto)
deriving stock (Hash GenesisKey -> Hash GenesisKey -> Bool
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)
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
Ord)
deriving (Int -> Hash GenesisKey -> ShowS
[Hash GenesisKey] -> ShowS
Hash GenesisKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisKey
$cfromString :: String -> Hash GenesisKey
IsString) via UsingRawBytesHex (Hash GenesisKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash GenesisKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisKey)
FromCBOR) via UsingRawBytes (Hash GenesisKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisKey) where
serialiseToRawBytes :: Hash GenesisKey -> ByteString
serialiseToRawBytes (GenesisKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash GenesisKey)
deserialiseFromRawBytes (AsHash AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'Genesis StandardCrypto -> Hash GenesisKey
GenesisKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisKey) where
textEnvelopeType :: AsType (SigningKey GenesisKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisKey)
_ = TextEnvelopeType
"GenesisSigningKey_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole GenesisKey PaymentKey where
castVerificationKey :: VerificationKey GenesisKey -> VerificationKey PaymentKey
castVerificationKey (GenesisVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)
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
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)
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
SerialiseAsCBOR
deriving (Int -> VerificationKey GenesisExtendedKey -> ShowS
[VerificationKey GenesisExtendedKey] -> ShowS
VerificationKey GenesisExtendedKey -> String
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
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)
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
SerialiseAsCBOR
deriving (Int -> SigningKey GenesisExtendedKey -> ShowS
[SigningKey GenesisExtendedKey] -> ShowS
SigningKey GenesisExtendedKey -> String
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
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
R:AsTypeGenesisExtendedKey
AsGenesisExtendedKey Seed
seed =
XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey
(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
R:AsTypeGenesisExtendedKey
AsGenesisExtendedKey = Word
32
getVerificationKey :: SigningKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey
getVerificationKey :: SigningKey GenesisExtendedKey -> VerificationKey GenesisExtendedKey
getVerificationKey (GenesisExtendedSigningKey XPrv
sk) =
XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey (HasCallStack => XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey GenesisExtendedKey
-> Hash GenesisExtendedKey
verificationKeyHash :: VerificationKey GenesisExtendedKey -> Hash GenesisExtendedKey
verificationKeyHash (GenesisExtendedVerificationKey XPub
vk) =
KeyHash 'Staking StandardCrypto -> Hash GenesisExtendedKey
GenesisExtendedKeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a b. Hash h a -> Hash h b
Crypto.castHash
forall a b. (a -> b) -> a -> b
$ 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
xpub) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey GenesisExtendedKey) where
fromCBOR :: forall s. Decoder s (VerificationKey GenesisExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return 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
xprv) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey GenesisExtendedKey) where
fromCBOR :: forall s. Decoder s (SigningKey GenesisExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey)
(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) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either
SerialiseAsRawBytesError (VerificationKey GenesisExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisExtendedKey
R:AsTypeGenesisExtendedKey
AsGenesisExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisExtendedKey")) forall a b. (a -> b) -> a -> b
$
XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKeyforall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisExtendedKey) where
serialiseToRawBytes :: SigningKey GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedSigningKey XPrv
xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisExtendedKey
R:AsTypeGenesisExtendedKey
AsGenesisExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (\String
msg -> String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError (String
"Unable to deserialise SigningKey GenesisExtendedKey" forall a. [a] -> [a] -> [a]
++ String
msg)) forall a b. (a -> b) -> a -> b
$
XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs
newtype instance Hash GenesisExtendedKey =
GenesisExtendedKeyHash (Shelley.KeyHash Shelley.Staking StandardCrypto)
deriving stock (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
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)
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
Ord)
deriving (Int -> Hash GenesisExtendedKey -> ShowS
[Hash GenesisExtendedKey] -> ShowS
Hash GenesisExtendedKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisExtendedKey
$cfromString :: String -> Hash GenesisExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisExtendedKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash GenesisExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisExtendedKey)
FromCBOR) via UsingRawBytes (Hash GenesisExtendedKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisExtendedKey) where
serialiseToRawBytes :: Hash GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash GenesisExtendedKey)
deserialiseFromRawBytes (AsHash AsType GenesisExtendedKey
R:AsTypeGenesisExtendedKey
AsGenesisExtendedKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisExtendedKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'Staking StandardCrypto -> Hash GenesisExtendedKey
GenesisExtendedKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 XPub
vk) =
VKey 'Genesis StandardCrypto -> VerificationKey GenesisKey
GenesisVerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall {a}. a
impossible
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley 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 (Shelley.VKey Shelley.GenesisDelegate StandardCrypto)
deriving stock (VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
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
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
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisDelegateKey
$cfromString :: String -> VerificationKey GenesisDelegateKey
IsString) via UsingRawBytesHex (VerificationKey GenesisDelegateKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (VerificationKey GenesisDelegateKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
newtype SigningKey GenesisDelegateKey =
GenesisDelegateSigningKey (Shelley.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisDelegateKey -> ShowS
[SigningKey GenesisDelegateKey] -> ShowS
SigningKey GenesisDelegateKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisDelegateKey
$cfromString :: String -> SigningKey GenesisDelegateKey
IsString) via UsingRawBytesHex (SigningKey GenesisDelegateKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (SigningKey GenesisDelegateKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisDelegateKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisDelegateKey -> Crypto.Seed -> SigningKey GenesisDelegateKey
deterministicSigningKey :: AsType GenesisDelegateKey -> Seed -> SigningKey GenesisDelegateKey
deterministicSigningKey AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisDelegateKey
GenesisDelegateSigningKey (forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word
deterministicSigningKeySeedSize AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey =
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
proxy
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey
getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey
getVerificationKey (GenesisDelegateSigningKey SignKeyDSIGN StandardCrypto
sk) =
VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey (forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
sk))
verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey
verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey
verificationKeyHash (GenesisDelegateVerificationKey VKey 'GenesisDelegate StandardCrypto
vkey) =
KeyHash 'GenesisDelegate StandardCrypto -> Hash GenesisDelegateKey
GenesisDelegateKeyHash (forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Shelley.hashKey VKey 'GenesisDelegate StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) where
serialiseToRawBytes :: VerificationKey GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either
SerialiseAsRawBytesError (VerificationKey GenesisDelegateKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisDelegateKey") forall a b. (a -> b) -> a -> b
$
VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisDelegateKey) where
serialiseToRawBytes :: SigningKey GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateSigningKey SignKeyDSIGN StandardCrypto
sk) =
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisDelegateKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey GenesisDelegateKey") forall a b. (a -> b) -> a -> b
$
SignKeyDSIGN StandardCrypto -> SigningKey GenesisDelegateKey
GenesisDelegateSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisDelegateKey =
GenesisDelegateKeyHash (Shelley.KeyHash Shelley.GenesisDelegate StandardCrypto)
deriving stock (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
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)
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
Ord)
deriving (Int -> Hash GenesisDelegateKey -> ShowS
[Hash GenesisDelegateKey] -> ShowS
Hash GenesisDelegateKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisDelegateKey
$cfromString :: String -> Hash GenesisDelegateKey
IsString) via UsingRawBytesHex (Hash GenesisDelegateKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash GenesisDelegateKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisDelegateKey)
FromCBOR) via UsingRawBytes (Hash GenesisDelegateKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisDelegateKey) where
serialiseToRawBytes :: Hash GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisDelegateKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash GenesisDelegateKey)
deserialiseFromRawBytes (AsHash AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisDelegateKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'GenesisDelegate StandardCrypto -> Hash GenesisDelegateKey
GenesisDelegateKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisDelegateKey) where
textEnvelopeType :: AsType (SigningKey GenesisDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisDelegateKey)
_ = TextEnvelopeType
"GenesisDelegateSigningKey_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole GenesisDelegateKey StakePoolKey where
castVerificationKey :: VerificationKey GenesisDelegateKey -> VerificationKey StakePoolKey
castVerificationKey (GenesisDelegateVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)) =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole GenesisDelegateKey StakePoolKey where
castSigningKey :: SigningKey GenesisDelegateKey -> SigningKey StakePoolKey
castSigningKey (GenesisDelegateSigningKey SignKeyDSIGN StandardCrypto
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
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)
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
SerialiseAsCBOR
deriving (Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
[VerificationKey GenesisDelegateExtendedKey] -> ShowS
VerificationKey GenesisDelegateExtendedKey -> String
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
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)
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
SerialiseAsCBOR
deriving (Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
[SigningKey GenesisDelegateExtendedKey] -> ShowS
SigningKey GenesisDelegateExtendedKey -> String
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
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
R:AsTypeGenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey Seed
seed =
XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey
(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
R:AsTypeGenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey = Word
32
getVerificationKey :: SigningKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey
getVerificationKey :: SigningKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey
getVerificationKey (GenesisDelegateExtendedSigningKey XPrv
sk) =
XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey (HasCallStack => XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)
verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
verificationKeyHash (GenesisDelegateExtendedVerificationKey XPub
vk) =
KeyHash 'Staking StandardCrypto -> Hash GenesisDelegateExtendedKey
GenesisDelegateExtendedKeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h a b. Hash h a -> Hash h b
Crypto.castHash
forall a b. (a -> b) -> a -> b
$ 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
xpub) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)
instance FromCBOR (VerificationKey GenesisDelegateExtendedKey) where
fromCBOR :: forall s. Decoder s (VerificationKey GenesisDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return 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
xprv) =
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)
instance FromCBOR (SigningKey GenesisDelegateExtendedKey) where
fromCBOR :: forall s. Decoder s (SigningKey GenesisDelegateExtendedKey)
fromCBOR = do
ByteString
bs <- forall a s. FromCBOR a => Decoder s a
fromCBOR
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey)
(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) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xpub
deserialiseFromRawBytes :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either
SerialiseAsRawBytesError
(VerificationKey GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisDelegateExtendedKey
R:AsTypeGenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (\String
msg -> String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError (String
"Unable to deserialise VerificationKey GenesisDelegateExtendedKey: " forall a. [a] -> [a] -> [a]
++ String
msg)) forall a b. (a -> b) -> a -> b
$
XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) where
serialiseToRawBytes :: SigningKey GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedSigningKey XPrv
xprv) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv
deserialiseFromRawBytes :: AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either
SerialiseAsRawBytesError (SigningKey GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisDelegateExtendedKey
R:AsTypeGenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey) ByteString
bs =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (\String
msg -> String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError (String
"Unable to deserialise SigningKey GenesisDelegateExtendedKey: " forall a. [a] -> [a] -> [a]
++ String
msg)) forall a b. (a -> b) -> a -> b
$
XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs
newtype instance Hash GenesisDelegateExtendedKey =
GenesisDelegateExtendedKeyHash (Shelley.KeyHash Shelley.Staking StandardCrypto)
deriving stock (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
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)
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
Ord)
deriving (Int -> Hash GenesisDelegateExtendedKey -> ShowS
[Hash GenesisDelegateExtendedKey] -> ShowS
Hash GenesisDelegateExtendedKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisDelegateExtendedKey
$cfromString :: String -> Hash GenesisDelegateExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisDelegateExtendedKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash GenesisDelegateExtendedKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisDelegateExtendedKey)
FromCBOR) via UsingRawBytes (Hash GenesisDelegateExtendedKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) where
serialiseToRawBytes :: Hash GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either
SerialiseAsRawBytesError (Hash GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsHash AsType GenesisDelegateExtendedKey
R:AsTypeGenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisDelegateExtendedKey: ") forall a b. (a -> b) -> a -> b
$
KeyHash 'Staking StandardCrypto -> Hash GenesisDelegateExtendedKey
GenesisDelegateExtendedKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 XPub
vk) =
VKey 'GenesisDelegate StandardCrypto
-> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe forall {a}. a
impossible
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
where
impossible :: a
impossible =
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley 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 (Shelley.VKey Shelley.Payment StandardCrypto)
deriving stock (VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
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
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
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey GenesisUTxOKey
$cfromString :: String -> VerificationKey GenesisUTxOKey
IsString) via UsingRawBytesHex (VerificationKey GenesisUTxOKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (VerificationKey GenesisUTxOKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisUTxOKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
newtype SigningKey GenesisUTxOKey =
GenesisUTxOSigningKey (Shelley.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey GenesisUTxOKey -> ShowS
[SigningKey GenesisUTxOKey] -> ShowS
SigningKey GenesisUTxOKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey GenesisUTxOKey
$cfromString :: String -> SigningKey GenesisUTxOKey
IsString) via UsingRawBytesHex (SigningKey GenesisUTxOKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (SigningKey GenesisUTxOKey)
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisUTxOKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deterministicSigningKey :: AsType GenesisUTxOKey -> Crypto.Seed -> SigningKey GenesisUTxOKey
deterministicSigningKey :: AsType GenesisUTxOKey -> Seed -> SigningKey GenesisUTxOKey
deterministicSigningKey AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey GenesisUTxOKey
GenesisUTxOSigningKey (forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word
deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word
deterministicSigningKeySeedSize AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey =
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
proxy
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey
getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey
getVerificationKey (GenesisUTxOSigningKey SignKeyDSIGN StandardCrypto
sk) =
VKey 'Payment StandardCrypto -> VerificationKey GenesisUTxOKey
GenesisUTxOVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey (forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
sk))
verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey
verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey
verificationKeyHash (GenesisUTxOVerificationKey VKey 'Payment StandardCrypto
vkey) =
KeyHash 'Payment StandardCrypto -> Hash GenesisUTxOKey
GenesisUTxOKeyHash (forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Shelley.hashKey VKey 'Payment StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) where
serialiseToRawBytes :: VerificationKey GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
vk
deserialiseFromRawBytes :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey GenesisUTxOKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Enable to deserialise VerificationKey GenesisUTxOKey") forall a b. (a -> b) -> a -> b
$
VKey 'Payment StandardCrypto -> VerificationKey GenesisUTxOKey
GenesisUTxOVerificationKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey GenesisUTxOKey) where
serialiseToRawBytes :: SigningKey GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOSigningKey SignKeyDSIGN StandardCrypto
sk) =
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
sk
deserialiseFromRawBytes :: AsType (SigningKey GenesisUTxOKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisUTxOKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey GenesisUTxOKey") forall a b. (a -> b) -> a -> b
$
SignKeyDSIGN StandardCrypto -> SigningKey GenesisUTxOKey
GenesisUTxOSigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs
newtype instance Hash GenesisUTxOKey =
GenesisUTxOKeyHash (Shelley.KeyHash Shelley.Payment StandardCrypto)
deriving stock (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
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)
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
Ord)
deriving (Int -> Hash GenesisUTxOKey -> ShowS
[Hash GenesisUTxOKey] -> ShowS
Hash GenesisUTxOKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash GenesisUTxOKey
$cfromString :: String -> Hash GenesisUTxOKey
IsString) via UsingRawBytesHex (Hash GenesisUTxOKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash GenesisUTxOKey)
$cfromCBOR :: forall s. Decoder s (Hash GenesisUTxOKey)
FromCBOR) via UsingRawBytes (Hash GenesisUTxOKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash GenesisUTxOKey) where
serialiseToRawBytes :: Hash GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash GenesisUTxOKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash GenesisUTxOKey)
deserialiseFromRawBytes (AsHash AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisUTxOKey") forall a b. (a -> b) -> a -> b
$
KeyHash 'Payment StandardCrypto -> Hash GenesisUTxOKey
GenesisUTxOKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey GenesisUTxOKey) where
textEnvelopeType :: AsType (SigningKey GenesisUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisUTxOKey)
_ = TextEnvelopeType
"GenesisUTxOSigningKey_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance CastVerificationKeyRole GenesisUTxOKey PaymentKey where
castVerificationKey :: VerificationKey GenesisUTxOKey -> VerificationKey PaymentKey
castVerificationKey (GenesisUTxOVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)) =
VKey 'Payment StandardCrypto -> VerificationKey PaymentKey
PaymentVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vkey)
instance CastSigningKeyRole GenesisUTxOKey PaymentKey where
castSigningKey :: SigningKey GenesisUTxOKey -> SigningKey PaymentKey
castSigningKey (GenesisUTxOSigningKey SignKeyDSIGN StandardCrypto
skey) =
SignKeyDSIGN StandardCrypto -> SigningKey PaymentKey
PaymentSigningKey SignKeyDSIGN StandardCrypto
skey
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 (Shelley.VKey Shelley.StakePool StandardCrypto)
deriving stock (VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
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
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
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey StakePoolKey
$cfromString :: String -> VerificationKey StakePoolKey
IsString) via UsingRawBytesHex (VerificationKey StakePoolKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (VerificationKey StakePoolKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey StakePoolKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
newtype SigningKey StakePoolKey =
StakePoolSigningKey (Shelley.SignKeyDSIGN StandardCrypto)
deriving (Int -> SigningKey StakePoolKey -> ShowS
[SigningKey StakePoolKey] -> ShowS
SigningKey StakePoolKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey StakePoolKey
$cfromString :: String -> SigningKey StakePoolKey
IsString) via UsingRawBytesHex (SigningKey StakePoolKey)
deriving newtype (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (SigningKey StakePoolKey)
$cfromCBOR :: forall s. Decoder s (SigningKey StakePoolKey)
FromCBOR)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
deterministicSigningKey :: AsType StakePoolKey -> Crypto.Seed -> SigningKey StakePoolKey
deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey
deterministicSigningKey AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey Seed
seed =
SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
StakePoolSigningKey (forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)
deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word
deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word
deterministicSigningKeySeedSize AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey =
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy (DSIGN StandardCrypto)
proxy
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey
getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey
getVerificationKey (StakePoolSigningKey SignKeyDSIGN StandardCrypto
sk) =
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey (forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey (forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN StandardCrypto
sk))
verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey
verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey
verificationKeyHash (StakePoolVerificationKey VKey 'StakePool StandardCrypto
vkey) =
KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash (forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
Shelley.hashKey VKey 'StakePool StandardCrypto
vkey)
instance SerialiseAsRawBytes (VerificationKey StakePoolKey) where
serialiseToRawBytes :: VerificationKey StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolVerificationKey (Shelley.VKey VerKeyDSIGN (DSIGN StandardCrypto)
vk)) =
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN (DSIGN StandardCrypto)
vk
deserialiseFromRawBytes :: AsType (VerificationKey StakePoolKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey StakePoolKey)
deserialiseFromRawBytes (AsVerificationKey AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey StakePoolKey") forall a b. (a -> b) -> a -> b
$
VKey 'StakePool StandardCrypto -> VerificationKey StakePoolKey
StakePoolVerificationKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Shelley.VKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs
instance SerialiseAsRawBytes (SigningKey StakePoolKey) where
serialiseToRawBytes :: SigningKey StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolSigningKey SignKeyDSIGN StandardCrypto
sk) =
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN StandardCrypto
sk
deserialiseFromRawBytes :: AsType (SigningKey StakePoolKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
deserialiseFromRawBytes (AsSigningKey AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey) ByteString
bs =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey StakePoolKey"))
(forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignKeyDSIGN StandardCrypto -> SigningKey StakePoolKey
StakePoolSigningKey)
(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 { Hash StakePoolKey -> KeyHash 'StakePool StandardCrypto
unStakePoolKeyHash :: Shelley.KeyHash Shelley.StakePool StandardCrypto }
deriving stock (Hash StakePoolKey -> Hash StakePoolKey -> Bool
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)
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
Ord)
deriving (Int -> Hash StakePoolKey -> ShowS
[Hash StakePoolKey] -> ShowS
Hash StakePoolKey -> String
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
forall a. (String -> a) -> IsString a
fromString :: String -> Hash StakePoolKey
$cfromString :: String -> Hash StakePoolKey
IsString) via UsingRawBytesHex (Hash StakePoolKey)
deriving (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
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
ToCBOR, Typeable (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 :: forall s. Decoder s (Hash StakePoolKey)
$cfromCBOR :: forall s. Decoder s (Hash StakePoolKey)
FromCBOR) via UsingRawBytes (Hash StakePoolKey)
deriving anyclass HasTypeProxy (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
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash StakePoolKey) where
serialiseToRawBytes :: Hash StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolKeyHash (Shelley.KeyHash Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh)) =
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))
vkh
deserialiseFromRawBytes :: AsType (Hash StakePoolKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash StakePoolKey)
deserialiseFromRawBytes (AsHash AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey) ByteString
bs =
forall b a. b -> Maybe a -> Either b a
maybeToRight
(String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakePoolKey")
(KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
Shelley.KeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32
instance ToJSONKey (Hash StakePoolKey) where
toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey)
toJSONKey = forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32
instance FromJSON (Hash StakePoolKey) where
parseJSON :: Value -> Parser (Hash StakePoolKey)
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"PoolId" forall a b. (a -> b) -> a -> b
$ \Text
str ->
case forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 (forall a. AsType a -> AsType (Hash a)
AsHash AsType StakePoolKey
AsStakePoolKey) Text
str of
Left Bech32DecodeError
err ->
forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Error deserialising Hash StakePoolKey: " forall a. Semigroup a => a -> a -> a
<> Text -> String
Text.unpack Text
str forall a. Semigroup a => a -> a -> a
<>
String
" Error: " forall a. Semigroup a => a -> a -> a
<> forall e. Error e => e -> String
displayError Bech32DecodeError
err
Right Hash StakePoolKey
h -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Hash StakePoolKey
h
instance HasTextEnvelope (VerificationKey StakePoolKey) where
textEnvelopeType :: AsType (VerificationKey StakePoolKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey StakePoolKey)
_ = TextEnvelopeType
"StakePoolVerificationKey_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy
instance HasTextEnvelope (SigningKey StakePoolKey) where
textEnvelopeType :: AsType (SigningKey StakePoolKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakePoolKey)
_ = TextEnvelopeType
"StakePoolSigningKey_"
forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
Crypto.algorithmNameDSIGN Proxy (DSIGN StandardCrypto)
proxy)
where
proxy :: Proxy (Shelley.DSIGN StandardCrypto)
proxy :: Proxy (DSIGN StandardCrypto)
proxy = forall {k} (t :: k). Proxy t
Proxy