{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
-- The Shelley ledger uses promoted data kinds which we have to use, but we do
-- not export any from this API. We also use them unticked as nature intended.
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}

-- | Shelley key types and their 'Key' class instances
module Cardano.Api.Internal.Keys.Shelley
  ( -- * Key types
    CommitteeColdKey
  , CommitteeColdExtendedKey
  , CommitteeHotKey
  , CommitteeHotExtendedKey
  , DRepKey
  , DRepExtendedKey
  , PaymentKey
  , PaymentExtendedKey
  , StakeKey
  , StakeExtendedKey
  , StakePoolExtendedKey
  , StakePoolKey
  , GenesisKey
  , GenesisExtendedKey
  , GenesisDelegateKey
  , GenesisDelegateExtendedKey
  , GenesisUTxOKey

    -- * Data family instances
  , AsType (..)
  , VerificationKey (..)
  , SigningKey (..)
  , Hash (..)
  )
where

import Cardano.Api.Internal.Error
import Cardano.Api.Internal.HasTypeProxy
import Cardano.Api.Internal.Hash
import Cardano.Api.Internal.Keys.Class
import Cardano.Api.Internal.Pretty
import Cardano.Api.Internal.SerialiseBech32
import Cardano.Api.Internal.SerialiseCBOR
import Cardano.Api.Internal.SerialiseJSON
import Cardano.Api.Internal.SerialiseRaw
import Cardano.Api.Internal.SerialiseTextEnvelope
import Cardano.Api.Internal.SerialiseUsing

import Cardano.Crypto.DSIGN qualified as DSIGN
import Cardano.Crypto.DSIGN.Class qualified as Crypto
import Cardano.Crypto.Hash.Class qualified as Crypto
import Cardano.Crypto.Seed qualified as Crypto
import Cardano.Crypto.Wallet qualified as Crypto.HD
import Cardano.Ledger.Keys (DSIGN)
import Cardano.Ledger.Keys qualified as Shelley

import Data.Aeson.Types (ToJSONKey (..), toJSONKeyText, withText)
import Data.Bifunctor (first)
import Data.ByteString (ByteString)
import Data.ByteString qualified as BS
import Data.Either.Combinators (maybeToRight)
import Data.Maybe
import Data.String (IsString (..))

--
-- Shelley payment keys
--

-- | Shelley-era payment keys. Used for Shelley payment addresses and witnessing
-- transactions that spend from these addresses.
--
-- This is a type level tag, used with other interfaces like 'Key'.
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)
    deriving stock VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
(VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool)
-> (VerificationKey PaymentKey
    -> VerificationKey PaymentKey -> Bool)
-> Eq (VerificationKey PaymentKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
== :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
$c/= :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
/= :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool
Eq
    deriving (Int -> VerificationKey PaymentKey -> ShowS
[VerificationKey PaymentKey] -> ShowS
VerificationKey PaymentKey -> String
(Int -> VerificationKey PaymentKey -> ShowS)
-> (VerificationKey PaymentKey -> String)
-> ([VerificationKey PaymentKey] -> ShowS)
-> Show (VerificationKey PaymentKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey PaymentKey -> ShowS
showsPrec :: Int -> VerificationKey PaymentKey -> ShowS
$cshow :: VerificationKey PaymentKey -> String
show :: VerificationKey PaymentKey -> String
$cshowList :: [VerificationKey PaymentKey] -> ShowS
showList :: [VerificationKey PaymentKey] -> ShowS
Show, String -> VerificationKey PaymentKey
(String -> VerificationKey PaymentKey)
-> IsString (VerificationKey PaymentKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey PaymentKey
fromString :: String -> VerificationKey PaymentKey
IsString) via UsingRawBytesHex (VerificationKey PaymentKey)
    deriving newtype (Typeable (VerificationKey PaymentKey)
Typeable (VerificationKey PaymentKey) =>
(VerificationKey PaymentKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey PaymentKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey PaymentKey] -> Size)
-> ToCBOR (VerificationKey PaymentKey)
VerificationKey PaymentKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VerificationKey PaymentKey -> Encoding
toCBOR :: VerificationKey PaymentKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey PaymentKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey PaymentKey] -> Size
ToCBOR, Typeable (VerificationKey PaymentKey)
Typeable (VerificationKey PaymentKey) =>
(forall s. Decoder s (VerificationKey PaymentKey))
-> (Proxy (VerificationKey PaymentKey) -> Text)
-> FromCBOR (VerificationKey PaymentKey)
Proxy (VerificationKey PaymentKey) -> Text
forall s. Decoder s (VerificationKey PaymentKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey PaymentKey)
fromCBOR :: forall s. Decoder s (VerificationKey PaymentKey)
$clabel :: Proxy (VerificationKey PaymentKey) -> Text
label :: Proxy (VerificationKey PaymentKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey PaymentKey)
HasTypeProxy (VerificationKey PaymentKey) =>
(VerificationKey PaymentKey -> ByteString)
-> (AsType (VerificationKey PaymentKey)
    -> ByteString -> Either DecoderError (VerificationKey PaymentKey))
-> SerialiseAsCBOR (VerificationKey PaymentKey)
AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey)
VerificationKey PaymentKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey PaymentKey -> ByteString
serialiseToCBOR :: VerificationKey PaymentKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey)
deserialiseFromCBOR :: AsType (VerificationKey PaymentKey)
-> ByteString -> Either DecoderError (VerificationKey PaymentKey)
SerialiseAsCBOR

  newtype SigningKey PaymentKey
    = PaymentSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey PaymentKey -> ShowS
[SigningKey PaymentKey] -> ShowS
SigningKey PaymentKey -> String
(Int -> SigningKey PaymentKey -> ShowS)
-> (SigningKey PaymentKey -> String)
-> ([SigningKey PaymentKey] -> ShowS)
-> Show (SigningKey PaymentKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey PaymentKey -> ShowS
showsPrec :: Int -> SigningKey PaymentKey -> ShowS
$cshow :: SigningKey PaymentKey -> String
show :: SigningKey PaymentKey -> String
$cshowList :: [SigningKey PaymentKey] -> ShowS
showList :: [SigningKey PaymentKey] -> ShowS
Show, String -> SigningKey PaymentKey
(String -> SigningKey PaymentKey)
-> IsString (SigningKey PaymentKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey PaymentKey
fromString :: String -> SigningKey PaymentKey
IsString) via UsingRawBytesHex (SigningKey PaymentKey)
    deriving newtype (Typeable (SigningKey PaymentKey)
Typeable (SigningKey PaymentKey) =>
(SigningKey PaymentKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey PaymentKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey PaymentKey] -> Size)
-> ToCBOR (SigningKey PaymentKey)
SigningKey PaymentKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SigningKey PaymentKey -> Encoding
toCBOR :: SigningKey PaymentKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey PaymentKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey PaymentKey] -> Size
ToCBOR, Typeable (SigningKey PaymentKey)
Typeable (SigningKey PaymentKey) =>
(forall s. Decoder s (SigningKey PaymentKey))
-> (Proxy (SigningKey PaymentKey) -> Text)
-> FromCBOR (SigningKey PaymentKey)
Proxy (SigningKey PaymentKey) -> Text
forall s. Decoder s (SigningKey PaymentKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey PaymentKey)
fromCBOR :: forall s. Decoder s (SigningKey PaymentKey)
$clabel :: Proxy (SigningKey PaymentKey) -> Text
label :: Proxy (SigningKey PaymentKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey PaymentKey)
HasTypeProxy (SigningKey PaymentKey) =>
(SigningKey PaymentKey -> ByteString)
-> (AsType (SigningKey PaymentKey)
    -> ByteString -> Either DecoderError (SigningKey PaymentKey))
-> SerialiseAsCBOR (SigningKey PaymentKey)
AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey)
SigningKey PaymentKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey PaymentKey -> ByteString
serialiseToCBOR :: SigningKey PaymentKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey)
deserialiseFromCBOR :: AsType (SigningKey PaymentKey)
-> ByteString -> Either DecoderError (SigningKey PaymentKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType PaymentKey -> Crypto.Seed -> SigningKey PaymentKey
  deterministicSigningKey :: AsType PaymentKey -> Seed -> SigningKey PaymentKey
deterministicSigningKey AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey PaymentKey
PaymentSigningKey (Seed -> SignKeyDSIGN DSIGN
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 =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey
  getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey
getVerificationKey (PaymentSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'Payment -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey
  verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey
verificationKeyHash (PaymentVerificationKey VKey 'Payment
vkey) =
    KeyHash 'Payment -> Hash PaymentKey
PaymentKeyHash (VKey 'Payment -> KeyHash 'Payment
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'Payment
vkey)

instance SerialiseAsRawBytes (VerificationKey PaymentKey) where
  serialiseToRawBytes :: VerificationKey PaymentKey -> ByteString
serialiseToRawBytes (PaymentVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey PaymentKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
deserialiseFromRawBytes (AsVerificationKey AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey) ByteString
bs =
    Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
-> (VerKeyDSIGN DSIGN
    -> Either SerialiseAsRawBytesError (VerificationKey PaymentKey))
-> Maybe (VerKeyDSIGN DSIGN)
-> Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      (SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey PaymentKey"))
      (VerificationKey PaymentKey
-> Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
forall a b. b -> Either a b
Right (VerificationKey PaymentKey
 -> Either SerialiseAsRawBytesError (VerificationKey PaymentKey))
-> (VerKeyDSIGN DSIGN -> VerificationKey PaymentKey)
-> VerKeyDSIGN DSIGN
-> Either SerialiseAsRawBytesError (VerificationKey PaymentKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VKey 'Payment -> VerificationKey PaymentKey
PaymentVerificationKey (VKey 'Payment -> VerificationKey PaymentKey)
-> (VerKeyDSIGN DSIGN -> VKey 'Payment)
-> VerKeyDSIGN DSIGN
-> VerificationKey PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey)
      (ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs)

instance SerialiseAsRawBytes (SigningKey PaymentKey) where
  serialiseToRawBytes :: SigningKey PaymentKey -> ByteString
serialiseToRawBytes (PaymentSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey PaymentKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey PaymentKey)
deserialiseFromRawBytes (AsSigningKey AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey) ByteString
bs =
    Either SerialiseAsRawBytesError (SigningKey PaymentKey)
-> (SignKeyDSIGN DSIGN
    -> Either SerialiseAsRawBytesError (SigningKey PaymentKey))
-> Maybe (SignKeyDSIGN DSIGN)
-> Either SerialiseAsRawBytesError (SigningKey PaymentKey)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      (SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (SigningKey PaymentKey)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to serialise AsSigningKey AsPaymentKey"))
      (SigningKey PaymentKey
-> Either SerialiseAsRawBytesError (SigningKey PaymentKey)
forall a b. b -> Either a b
Right (SigningKey PaymentKey
 -> Either SerialiseAsRawBytesError (SigningKey PaymentKey))
-> (SignKeyDSIGN DSIGN -> SigningKey PaymentKey)
-> SignKeyDSIGN DSIGN
-> Either SerialiseAsRawBytesError (SigningKey PaymentKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignKeyDSIGN DSIGN -> SigningKey PaymentKey
PaymentSigningKey)
      (ByteString -> Maybe (SignKeyDSIGN DSIGN)
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 {Hash PaymentKey -> KeyHash 'Payment
unPaymentKeyHash :: Shelley.KeyHash Shelley.Payment}
  deriving stock (Hash PaymentKey -> Hash PaymentKey -> Bool
(Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> Eq (Hash PaymentKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash PaymentKey -> Hash PaymentKey -> Bool
== :: Hash PaymentKey -> Hash PaymentKey -> Bool
$c/= :: Hash PaymentKey -> Hash PaymentKey -> Bool
/= :: Hash PaymentKey -> Hash PaymentKey -> Bool
Eq, Eq (Hash PaymentKey)
Eq (Hash PaymentKey) =>
(Hash PaymentKey -> Hash PaymentKey -> Ordering)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Bool)
-> (Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey)
-> (Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey)
-> Ord (Hash PaymentKey)
Hash PaymentKey -> Hash PaymentKey -> Bool
Hash PaymentKey -> Hash PaymentKey -> Ordering
Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash PaymentKey -> Hash PaymentKey -> Ordering
compare :: Hash PaymentKey -> Hash PaymentKey -> Ordering
$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
>= :: Hash PaymentKey -> Hash PaymentKey -> Bool
$cmax :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
max :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
$cmin :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
min :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey
Ord)
  deriving (Int -> Hash PaymentKey -> ShowS
[Hash PaymentKey] -> ShowS
Hash PaymentKey -> String
(Int -> Hash PaymentKey -> ShowS)
-> (Hash PaymentKey -> String)
-> ([Hash PaymentKey] -> ShowS)
-> Show (Hash PaymentKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash PaymentKey -> ShowS
showsPrec :: Int -> Hash PaymentKey -> ShowS
$cshow :: Hash PaymentKey -> String
show :: Hash PaymentKey -> String
$cshowList :: [Hash PaymentKey] -> ShowS
showList :: [Hash PaymentKey] -> ShowS
Show, String -> Hash PaymentKey
(String -> Hash PaymentKey) -> IsString (Hash PaymentKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash PaymentKey
fromString :: String -> Hash PaymentKey
IsString) via UsingRawBytesHex (Hash PaymentKey)
  deriving (Typeable (Hash PaymentKey)
Typeable (Hash PaymentKey) =>
(Hash PaymentKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash PaymentKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash PaymentKey] -> Size)
-> ToCBOR (Hash PaymentKey)
Hash PaymentKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash PaymentKey -> Encoding
toCBOR :: Hash PaymentKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentKey] -> Size
ToCBOR, Typeable (Hash PaymentKey)
Typeable (Hash PaymentKey) =>
(forall s. Decoder s (Hash PaymentKey))
-> (Proxy (Hash PaymentKey) -> Text) -> FromCBOR (Hash PaymentKey)
Proxy (Hash PaymentKey) -> Text
forall s. Decoder s (Hash PaymentKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash PaymentKey)
fromCBOR :: forall s. Decoder s (Hash PaymentKey)
$clabel :: Proxy (Hash PaymentKey) -> Text
label :: Proxy (Hash PaymentKey) -> Text
FromCBOR) via UsingRawBytes (Hash PaymentKey)
  deriving (ToJSONKeyFunction [Hash PaymentKey]
ToJSONKeyFunction (Hash PaymentKey)
ToJSONKeyFunction (Hash PaymentKey)
-> ToJSONKeyFunction [Hash PaymentKey]
-> ToJSONKey (Hash PaymentKey)
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
$ctoJSONKey :: ToJSONKeyFunction (Hash PaymentKey)
toJSONKey :: ToJSONKeyFunction (Hash PaymentKey)
$ctoJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey]
toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey]
ToJSONKey, [Hash PaymentKey] -> Value
[Hash PaymentKey] -> Encoding
Hash PaymentKey -> Bool
Hash PaymentKey -> Value
Hash PaymentKey -> Encoding
(Hash PaymentKey -> Value)
-> (Hash PaymentKey -> Encoding)
-> ([Hash PaymentKey] -> Value)
-> ([Hash PaymentKey] -> Encoding)
-> (Hash PaymentKey -> Bool)
-> ToJSON (Hash PaymentKey)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Hash PaymentKey -> Value
toJSON :: Hash PaymentKey -> Value
$ctoEncoding :: Hash PaymentKey -> Encoding
toEncoding :: Hash PaymentKey -> Encoding
$ctoJSONList :: [Hash PaymentKey] -> Value
toJSONList :: [Hash PaymentKey] -> Value
$ctoEncodingList :: [Hash PaymentKey] -> Encoding
toEncodingList :: [Hash PaymentKey] -> Encoding
$comitField :: Hash PaymentKey -> Bool
omitField :: Hash PaymentKey -> Bool
ToJSON, Maybe (Hash PaymentKey)
Value -> Parser [Hash PaymentKey]
Value -> Parser (Hash PaymentKey)
(Value -> Parser (Hash PaymentKey))
-> (Value -> Parser [Hash PaymentKey])
-> Maybe (Hash PaymentKey)
-> FromJSON (Hash PaymentKey)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser (Hash PaymentKey)
parseJSON :: Value -> Parser (Hash PaymentKey)
$cparseJSONList :: Value -> Parser [Hash PaymentKey]
parseJSONList :: Value -> Parser [Hash PaymentKey]
$comittedField :: Maybe (Hash PaymentKey)
omittedField :: Maybe (Hash PaymentKey)
FromJSON) via UsingRawBytesHex (Hash PaymentKey)
  deriving anyclass HasTypeProxy (Hash PaymentKey)
HasTypeProxy (Hash PaymentKey) =>
(Hash PaymentKey -> ByteString)
-> (AsType (Hash PaymentKey)
    -> ByteString -> Either DecoderError (Hash PaymentKey))
-> SerialiseAsCBOR (Hash PaymentKey)
AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey)
Hash PaymentKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash PaymentKey -> ByteString
serialiseToCBOR :: Hash PaymentKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey)
deserialiseFromCBOR :: AsType (Hash PaymentKey)
-> ByteString -> Either DecoderError (Hash PaymentKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash PaymentKey) where
  serialiseToRawBytes :: Hash PaymentKey -> ByteString
serialiseToRawBytes (PaymentKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash PaymentKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash PaymentKey)
deserialiseFromRawBytes (AsHash AsType PaymentKey
R:AsTypePaymentKey
AsPaymentKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash PaymentKey)
-> Either SerialiseAsRawBytesError (Hash PaymentKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash PaymentKey")
      (KeyHash 'Payment -> Hash PaymentKey
PaymentKeyHash (KeyHash 'Payment -> Hash PaymentKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash PaymentKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash PaymentKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
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_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey PaymentKey) where
  textEnvelopeType :: AsType (SigningKey PaymentKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey PaymentKey)
_ =
    TextEnvelopeType
"PaymentSigningKeyShelley_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

--
-- Shelley payment extended ed25519 keys
--

-- | Shelley-era payment keys using extended ed25519 cryptographic keys.
--
-- They can be used for Shelley payment addresses and witnessing
-- transactions that spend from these addresses.
--
-- These extended keys are used by HD wallets. So this type provides
-- interoperability with HD wallets. The ITN CLI also supported this key type.
--
-- The extended verification keys can be converted (via 'castVerificationKey')
-- to ordinary keys (i.e. 'VerificationKey' 'PaymentKey') but this is /not/ the
-- case for the signing keys. The signing keys can be used to witness
-- transactions directly, with verification via their non-extended verification
-- key ('VerificationKey' 'PaymentKey').
--
-- This is a type level tag, used with other interfaces like 'Key'.
data PaymentExtendedKey

instance HasTypeProxy PaymentExtendedKey where
  data AsType PaymentExtendedKey = AsPaymentExtendedKey
  proxyToAsType :: Proxy PaymentExtendedKey -> AsType PaymentExtendedKey
proxyToAsType Proxy PaymentExtendedKey
_ = AsType PaymentExtendedKey
AsPaymentExtendedKey

instance Key PaymentExtendedKey where
  newtype VerificationKey PaymentExtendedKey
    = PaymentExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
(VerificationKey PaymentExtendedKey
 -> VerificationKey PaymentExtendedKey -> Bool)
-> (VerificationKey PaymentExtendedKey
    -> VerificationKey PaymentExtendedKey -> Bool)
-> Eq (VerificationKey PaymentExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
== :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
$c/= :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
/= :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey PaymentExtendedKey)
HasTypeProxy (VerificationKey PaymentExtendedKey) =>
(VerificationKey PaymentExtendedKey -> ByteString)
-> (AsType (VerificationKey PaymentExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey PaymentExtendedKey))
-> SerialiseAsCBOR (VerificationKey PaymentExtendedKey)
AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey)
VerificationKey PaymentExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey PaymentExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey PaymentExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey PaymentExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey PaymentExtendedKey -> ShowS
[VerificationKey PaymentExtendedKey] -> ShowS
VerificationKey PaymentExtendedKey -> String
(Int -> VerificationKey PaymentExtendedKey -> ShowS)
-> (VerificationKey PaymentExtendedKey -> String)
-> ([VerificationKey PaymentExtendedKey] -> ShowS)
-> Show (VerificationKey PaymentExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS
$cshow :: VerificationKey PaymentExtendedKey -> String
show :: VerificationKey PaymentExtendedKey -> String
$cshowList :: [VerificationKey PaymentExtendedKey] -> ShowS
showList :: [VerificationKey PaymentExtendedKey] -> ShowS
Show, String -> VerificationKey PaymentExtendedKey
(String -> VerificationKey PaymentExtendedKey)
-> IsString (VerificationKey PaymentExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey PaymentExtendedKey
fromString :: String -> VerificationKey PaymentExtendedKey
IsString) via UsingRawBytesHex (VerificationKey PaymentExtendedKey)

  newtype SigningKey PaymentExtendedKey
    = PaymentExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey PaymentExtendedKey)
HasTypeProxy (SigningKey PaymentExtendedKey) =>
(SigningKey PaymentExtendedKey -> ByteString)
-> (AsType (SigningKey PaymentExtendedKey)
    -> ByteString
    -> Either DecoderError (SigningKey PaymentExtendedKey))
-> SerialiseAsCBOR (SigningKey PaymentExtendedKey)
AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey)
SigningKey PaymentExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey PaymentExtendedKey -> ByteString
serialiseToCBOR :: SigningKey PaymentExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey PaymentExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey PaymentExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey PaymentExtendedKey -> ShowS
[SigningKey PaymentExtendedKey] -> ShowS
SigningKey PaymentExtendedKey -> String
(Int -> SigningKey PaymentExtendedKey -> ShowS)
-> (SigningKey PaymentExtendedKey -> String)
-> ([SigningKey PaymentExtendedKey] -> ShowS)
-> Show (SigningKey PaymentExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS
showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS
$cshow :: SigningKey PaymentExtendedKey -> String
show :: SigningKey PaymentExtendedKey -> String
$cshowList :: [SigningKey PaymentExtendedKey] -> ShowS
showList :: [SigningKey PaymentExtendedKey] -> ShowS
Show, String -> SigningKey PaymentExtendedKey
(String -> SigningKey PaymentExtendedKey)
-> IsString (SigningKey PaymentExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey PaymentExtendedKey
fromString :: 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
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word
deterministicSigningKeySeedSize AsType PaymentExtendedKey
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
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey PaymentExtendedKey
    -> Hash PaymentExtendedKey
  verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey
verificationKeyHash (PaymentExtendedVerificationKey XPub
vk) =
    KeyHash 'Payment -> Hash PaymentExtendedKey
PaymentExtendedKeyHash
      (KeyHash 'Payment -> Hash PaymentExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'Payment)
-> Hash ADDRHASH XPub
-> Hash PaymentExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'Payment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash PaymentExtendedKey)
-> Hash ADDRHASH XPub -> Hash PaymentExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

instance ToCBOR (VerificationKey PaymentExtendedKey) where
  toCBOR :: VerificationKey PaymentExtendedKey -> Encoding
toCBOR (PaymentExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey PaymentExtendedKey))
-> (XPub -> Decoder s (VerificationKey PaymentExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey PaymentExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey PaymentExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey PaymentExtendedKey
-> Decoder s (VerificationKey PaymentExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey PaymentExtendedKey
 -> Decoder s (VerificationKey PaymentExtendedKey))
-> (XPub -> VerificationKey PaymentExtendedKey)
-> XPub
-> Decoder s (VerificationKey PaymentExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey PaymentExtendedKey) where
  toCBOR :: SigningKey PaymentExtendedKey -> Encoding
toCBOR (PaymentExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey PaymentExtendedKey))
-> (XPrv -> Decoder s (SigningKey PaymentExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey PaymentExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey PaymentExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey PaymentExtendedKey
-> Decoder s (SigningKey PaymentExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey PaymentExtendedKey
 -> Decoder s (SigningKey PaymentExtendedKey))
-> (XPrv -> SigningKey PaymentExtendedKey)
-> XPrv
-> Decoder s (SigningKey PaymentExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) where
  serialiseToRawBytes :: VerificationKey PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedVerificationKey XPub
xpub) =
    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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey PaymentExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey PaymentExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey PaymentExtendedKey"))
      (XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey (XPub -> VerificationKey PaymentExtendedKey)
-> Either String XPub
-> Either String (VerificationKey PaymentExtendedKey)
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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey PaymentExtendedKey)
-> Either SerialiseAsRawBytesError (SigningKey PaymentExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey PaymentExtendedKey"))
      (XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey (XPrv -> SigningKey PaymentExtendedKey)
-> Either String XPrv
-> Either String (SigningKey PaymentExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)

instance SerialiseAsBech32 (VerificationKey PaymentExtendedKey) where
  bech32PrefixFor :: VerificationKey PaymentExtendedKey -> Text
bech32PrefixFor VerificationKey PaymentExtendedKey
_ = Text
"addr_xvk"
  bech32PrefixesPermitted :: AsType (VerificationKey PaymentExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey PaymentExtendedKey)
_ = [Text
"addr_xvk"]

instance SerialiseAsBech32 (SigningKey PaymentExtendedKey) where
  bech32PrefixFor :: SigningKey PaymentExtendedKey -> Text
bech32PrefixFor SigningKey PaymentExtendedKey
_ = Text
"addr_xsk"
  bech32PrefixesPermitted :: AsType (SigningKey PaymentExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey PaymentExtendedKey)
_ = [Text
"addr_xsk"]

newtype instance Hash PaymentExtendedKey
  = PaymentExtendedKeyHash
  {Hash PaymentExtendedKey -> KeyHash 'Payment
unPaymentExtendedKeyHash :: Shelley.KeyHash Shelley.Payment}
  deriving stock (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
(Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> Eq (Hash PaymentExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
== :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$c/= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
/= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
Eq, Eq (Hash PaymentExtendedKey)
Eq (Hash PaymentExtendedKey) =>
(Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool)
-> (Hash PaymentExtendedKey
    -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey)
-> (Hash PaymentExtendedKey
    -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey)
-> Ord (Hash PaymentExtendedKey)
Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering
Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering
compare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering
$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
>= :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool
$cmax :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
max :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
$cmin :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
min :: Hash PaymentExtendedKey
-> Hash PaymentExtendedKey -> Hash PaymentExtendedKey
Ord)
  deriving (Int -> Hash PaymentExtendedKey -> ShowS
[Hash PaymentExtendedKey] -> ShowS
Hash PaymentExtendedKey -> String
(Int -> Hash PaymentExtendedKey -> ShowS)
-> (Hash PaymentExtendedKey -> String)
-> ([Hash PaymentExtendedKey] -> ShowS)
-> Show (Hash PaymentExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash PaymentExtendedKey -> ShowS
showsPrec :: Int -> Hash PaymentExtendedKey -> ShowS
$cshow :: Hash PaymentExtendedKey -> String
show :: Hash PaymentExtendedKey -> String
$cshowList :: [Hash PaymentExtendedKey] -> ShowS
showList :: [Hash PaymentExtendedKey] -> ShowS
Show, String -> Hash PaymentExtendedKey
(String -> Hash PaymentExtendedKey)
-> IsString (Hash PaymentExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash PaymentExtendedKey
fromString :: String -> Hash PaymentExtendedKey
IsString) via UsingRawBytesHex (Hash PaymentExtendedKey)
  deriving (Typeable (Hash PaymentExtendedKey)
Typeable (Hash PaymentExtendedKey) =>
(Hash PaymentExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash PaymentExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash PaymentExtendedKey] -> Size)
-> ToCBOR (Hash PaymentExtendedKey)
Hash PaymentExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash PaymentExtendedKey -> Encoding
toCBOR :: Hash PaymentExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash PaymentExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash PaymentExtendedKey] -> Size
ToCBOR, Typeable (Hash PaymentExtendedKey)
Typeable (Hash PaymentExtendedKey) =>
(forall s. Decoder s (Hash PaymentExtendedKey))
-> (Proxy (Hash PaymentExtendedKey) -> Text)
-> FromCBOR (Hash PaymentExtendedKey)
Proxy (Hash PaymentExtendedKey) -> Text
forall s. Decoder s (Hash PaymentExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash PaymentExtendedKey)
fromCBOR :: forall s. Decoder s (Hash PaymentExtendedKey)
$clabel :: Proxy (Hash PaymentExtendedKey) -> Text
label :: Proxy (Hash PaymentExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash PaymentExtendedKey)
  deriving anyclass HasTypeProxy (Hash PaymentExtendedKey)
HasTypeProxy (Hash PaymentExtendedKey) =>
(Hash PaymentExtendedKey -> ByteString)
-> (AsType (Hash PaymentExtendedKey)
    -> ByteString -> Either DecoderError (Hash PaymentExtendedKey))
-> SerialiseAsCBOR (Hash PaymentExtendedKey)
AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey)
Hash PaymentExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash PaymentExtendedKey -> ByteString
serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey)
deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey)
-> ByteString -> Either DecoderError (Hash PaymentExtendedKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash PaymentExtendedKey) where
  serialiseToRawBytes :: Hash PaymentExtendedKey -> ByteString
serialiseToRawBytes (PaymentExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash PaymentExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash PaymentExtendedKey)
deserialiseFromRawBytes (AsHash AsType PaymentExtendedKey
R:AsTypePaymentExtendedKey
AsPaymentExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash PaymentExtendedKey)
-> Either SerialiseAsRawBytesError (Hash PaymentExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash PaymentExtendedKey") (Maybe (Hash PaymentExtendedKey)
 -> Either SerialiseAsRawBytesError (Hash PaymentExtendedKey))
-> Maybe (Hash PaymentExtendedKey)
-> Either SerialiseAsRawBytesError (Hash PaymentExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Payment -> Hash PaymentExtendedKey
PaymentExtendedKeyHash (KeyHash 'Payment -> Hash PaymentExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash PaymentExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash PaymentExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash PaymentExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
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 -> VerificationKey PaymentKey
PaymentVerificationKey
      (VKey 'Payment -> VerificationKey PaymentKey)
-> (XPub -> VKey 'Payment) -> XPub -> VerificationKey PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'Payment)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'Payment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey PaymentKey)
-> XPub -> VerificationKey PaymentKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley key sizes do not match!"

--
-- Stake keys
--

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
unStakeVerificationKey :: Shelley.VKey Shelley.Staking
    }
    deriving stock VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
(VerificationKey StakeKey -> VerificationKey StakeKey -> Bool)
-> (VerificationKey StakeKey -> VerificationKey StakeKey -> Bool)
-> Eq (VerificationKey StakeKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
== :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
$c/= :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
/= :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool
Eq
    deriving newtype (Typeable (VerificationKey StakeKey)
Typeable (VerificationKey StakeKey) =>
(VerificationKey StakeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey StakeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey StakeKey] -> Size)
-> ToCBOR (VerificationKey StakeKey)
VerificationKey StakeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VerificationKey StakeKey -> Encoding
toCBOR :: VerificationKey StakeKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakeKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakeKey] -> Size
ToCBOR, Typeable (VerificationKey StakeKey)
Typeable (VerificationKey StakeKey) =>
(forall s. Decoder s (VerificationKey StakeKey))
-> (Proxy (VerificationKey StakeKey) -> Text)
-> FromCBOR (VerificationKey StakeKey)
Proxy (VerificationKey StakeKey) -> Text
forall s. Decoder s (VerificationKey StakeKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey StakeKey)
fromCBOR :: forall s. Decoder s (VerificationKey StakeKey)
$clabel :: Proxy (VerificationKey StakeKey) -> Text
label :: Proxy (VerificationKey StakeKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey StakeKey)
HasTypeProxy (VerificationKey StakeKey) =>
(VerificationKey StakeKey -> ByteString)
-> (AsType (VerificationKey StakeKey)
    -> ByteString -> Either DecoderError (VerificationKey StakeKey))
-> SerialiseAsCBOR (VerificationKey StakeKey)
AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey)
VerificationKey StakeKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey StakeKey -> ByteString
serialiseToCBOR :: VerificationKey StakeKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey)
deserialiseFromCBOR :: AsType (VerificationKey StakeKey)
-> ByteString -> Either DecoderError (VerificationKey StakeKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey StakeKey -> ShowS
[VerificationKey StakeKey] -> ShowS
VerificationKey StakeKey -> String
(Int -> VerificationKey StakeKey -> ShowS)
-> (VerificationKey StakeKey -> String)
-> ([VerificationKey StakeKey] -> ShowS)
-> Show (VerificationKey StakeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey StakeKey -> ShowS
showsPrec :: Int -> VerificationKey StakeKey -> ShowS
$cshow :: VerificationKey StakeKey -> String
show :: VerificationKey StakeKey -> String
$cshowList :: [VerificationKey StakeKey] -> ShowS
showList :: [VerificationKey StakeKey] -> ShowS
Show, String -> VerificationKey StakeKey
(String -> VerificationKey StakeKey)
-> IsString (VerificationKey StakeKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey StakeKey
fromString :: String -> VerificationKey StakeKey
IsString) via UsingRawBytesHex (VerificationKey StakeKey)

  newtype SigningKey StakeKey
    = StakeSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving newtype (Typeable (SigningKey StakeKey)
Typeable (SigningKey StakeKey) =>
(SigningKey StakeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey StakeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey StakeKey] -> Size)
-> ToCBOR (SigningKey StakeKey)
SigningKey StakeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SigningKey StakeKey -> Encoding
toCBOR :: SigningKey StakeKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakeKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakeKey] -> Size
ToCBOR, Typeable (SigningKey StakeKey)
Typeable (SigningKey StakeKey) =>
(forall s. Decoder s (SigningKey StakeKey))
-> (Proxy (SigningKey StakeKey) -> Text)
-> FromCBOR (SigningKey StakeKey)
Proxy (SigningKey StakeKey) -> Text
forall s. Decoder s (SigningKey StakeKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey StakeKey)
fromCBOR :: forall s. Decoder s (SigningKey StakeKey)
$clabel :: Proxy (SigningKey StakeKey) -> Text
label :: Proxy (SigningKey StakeKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey StakeKey)
HasTypeProxy (SigningKey StakeKey) =>
(SigningKey StakeKey -> ByteString)
-> (AsType (SigningKey StakeKey)
    -> ByteString -> Either DecoderError (SigningKey StakeKey))
-> SerialiseAsCBOR (SigningKey StakeKey)
AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey)
SigningKey StakeKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey StakeKey -> ByteString
serialiseToCBOR :: SigningKey StakeKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey)
deserialiseFromCBOR :: AsType (SigningKey StakeKey)
-> ByteString -> Either DecoderError (SigningKey StakeKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey StakeKey -> ShowS
[SigningKey StakeKey] -> ShowS
SigningKey StakeKey -> String
(Int -> SigningKey StakeKey -> ShowS)
-> (SigningKey StakeKey -> String)
-> ([SigningKey StakeKey] -> ShowS)
-> Show (SigningKey StakeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey StakeKey -> ShowS
showsPrec :: Int -> SigningKey StakeKey -> ShowS
$cshow :: SigningKey StakeKey -> String
show :: SigningKey StakeKey -> String
$cshowList :: [SigningKey StakeKey] -> ShowS
showList :: [SigningKey StakeKey] -> ShowS
Show, String -> SigningKey StakeKey
(String -> SigningKey StakeKey) -> IsString (SigningKey StakeKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey StakeKey
fromString :: 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 DSIGN -> SigningKey StakeKey
StakeSigningKey (Seed -> SignKeyDSIGN DSIGN
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 =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey
  getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey
getVerificationKey (StakeSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'Staking -> VerificationKey StakeKey
StakeVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Staking
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey
  verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey
verificationKeyHash (StakeVerificationKey VKey 'Staking
vkey) =
    KeyHash 'Staking -> Hash StakeKey
StakeKeyHash (VKey 'Staking -> KeyHash 'Staking
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'Staking
vkey)

instance SerialiseAsRawBytes (VerificationKey StakeKey) where
  serialiseToRawBytes :: VerificationKey StakeKey -> ByteString
serialiseToRawBytes (StakeVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey StakeKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey StakeKey)
deserialiseFromRawBytes (AsVerificationKey AsType StakeKey
R:AsTypeStakeKey
AsStakeKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey StakeKey)
-> Either SerialiseAsRawBytesError (VerificationKey StakeKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey StakeKey") (Maybe (VerificationKey StakeKey)
 -> Either SerialiseAsRawBytesError (VerificationKey StakeKey))
-> Maybe (VerificationKey StakeKey)
-> Either SerialiseAsRawBytesError (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$
      VKey 'Staking -> VerificationKey StakeKey
StakeVerificationKey (VKey 'Staking -> VerificationKey StakeKey)
-> (VerKeyDSIGN DSIGN -> VKey 'Staking)
-> VerKeyDSIGN DSIGN
-> VerificationKey StakeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Staking
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey StakeKey)
-> Maybe (VerKeyDSIGN DSIGN) -> Maybe (VerificationKey StakeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey StakeKey) where
  serialiseToRawBytes :: SigningKey StakeKey -> ByteString
serialiseToRawBytes (StakeSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey StakeKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey StakeKey)
deserialiseFromRawBytes (AsSigningKey AsType StakeKey
R:AsTypeStakeKey
AsStakeKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (SigningKey StakeKey)
-> Either SerialiseAsRawBytesError (SigningKey StakeKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey StakeKey") (Maybe (SigningKey StakeKey)
 -> Either SerialiseAsRawBytesError (SigningKey StakeKey))
-> Maybe (SigningKey StakeKey)
-> Either SerialiseAsRawBytesError (SigningKey StakeKey)
forall a b. (a -> b) -> a -> b
$
      SignKeyDSIGN DSIGN -> SigningKey StakeKey
StakeSigningKey (SignKeyDSIGN DSIGN -> SigningKey StakeKey)
-> Maybe (SignKeyDSIGN DSIGN) -> Maybe (SigningKey StakeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN DSIGN)
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 {Hash StakeKey -> KeyHash 'Staking
unStakeKeyHash :: Shelley.KeyHash Shelley.Staking}
  deriving stock (Hash StakeKey -> Hash StakeKey -> Bool
(Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool) -> Eq (Hash StakeKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash StakeKey -> Hash StakeKey -> Bool
== :: Hash StakeKey -> Hash StakeKey -> Bool
$c/= :: Hash StakeKey -> Hash StakeKey -> Bool
/= :: Hash StakeKey -> Hash StakeKey -> Bool
Eq, Eq (Hash StakeKey)
Eq (Hash StakeKey) =>
(Hash StakeKey -> Hash StakeKey -> Ordering)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Bool)
-> (Hash StakeKey -> Hash StakeKey -> Hash StakeKey)
-> (Hash StakeKey -> Hash StakeKey -> Hash StakeKey)
-> Ord (Hash StakeKey)
Hash StakeKey -> Hash StakeKey -> Bool
Hash StakeKey -> Hash StakeKey -> Ordering
Hash StakeKey -> Hash StakeKey -> Hash StakeKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash StakeKey -> Hash StakeKey -> Ordering
compare :: Hash StakeKey -> Hash StakeKey -> Ordering
$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
>= :: Hash StakeKey -> Hash StakeKey -> Bool
$cmax :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
max :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
$cmin :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
min :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey
Ord)
  deriving (Int -> Hash StakeKey -> ShowS
[Hash StakeKey] -> ShowS
Hash StakeKey -> String
(Int -> Hash StakeKey -> ShowS)
-> (Hash StakeKey -> String)
-> ([Hash StakeKey] -> ShowS)
-> Show (Hash StakeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash StakeKey -> ShowS
showsPrec :: Int -> Hash StakeKey -> ShowS
$cshow :: Hash StakeKey -> String
show :: Hash StakeKey -> String
$cshowList :: [Hash StakeKey] -> ShowS
showList :: [Hash StakeKey] -> ShowS
Show, String -> Hash StakeKey
(String -> Hash StakeKey) -> IsString (Hash StakeKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash StakeKey
fromString :: String -> Hash StakeKey
IsString) via UsingRawBytesHex (Hash StakeKey)
  deriving (Typeable (Hash StakeKey)
Typeable (Hash StakeKey) =>
(Hash StakeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash StakeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash StakeKey] -> Size)
-> ToCBOR (Hash StakeKey)
Hash StakeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash StakeKey -> Encoding
toCBOR :: Hash StakeKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeKey] -> Size
ToCBOR, Typeable (Hash StakeKey)
Typeable (Hash StakeKey) =>
(forall s. Decoder s (Hash StakeKey))
-> (Proxy (Hash StakeKey) -> Text) -> FromCBOR (Hash StakeKey)
Proxy (Hash StakeKey) -> Text
forall s. Decoder s (Hash StakeKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash StakeKey)
fromCBOR :: forall s. Decoder s (Hash StakeKey)
$clabel :: Proxy (Hash StakeKey) -> Text
label :: Proxy (Hash StakeKey) -> Text
FromCBOR) via UsingRawBytes (Hash StakeKey)
  deriving anyclass HasTypeProxy (Hash StakeKey)
HasTypeProxy (Hash StakeKey) =>
(Hash StakeKey -> ByteString)
-> (AsType (Hash StakeKey)
    -> ByteString -> Either DecoderError (Hash StakeKey))
-> SerialiseAsCBOR (Hash StakeKey)
AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey)
Hash StakeKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash StakeKey -> ByteString
serialiseToCBOR :: Hash StakeKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey)
deserialiseFromCBOR :: AsType (Hash StakeKey)
-> ByteString -> Either DecoderError (Hash StakeKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash StakeKey) where
  serialiseToRawBytes :: Hash StakeKey -> ByteString
serialiseToRawBytes (StakeKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash StakeKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash StakeKey)
deserialiseFromRawBytes (AsHash AsType StakeKey
R:AsTypeStakeKey
AsStakeKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash StakeKey)
-> Either SerialiseAsRawBytesError (Hash StakeKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakeKey") (Maybe (Hash StakeKey)
 -> Either SerialiseAsRawBytesError (Hash StakeKey))
-> Maybe (Hash StakeKey)
-> Either SerialiseAsRawBytesError (Hash StakeKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Staking -> Hash StakeKey
StakeKeyHash (KeyHash 'Staking -> Hash StakeKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash StakeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash StakeKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash StakeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
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_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey StakeKey) where
  textEnvelopeType :: AsType (SigningKey StakeKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakeKey)
_ =
    TextEnvelopeType
"StakeSigningKeyShelley_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

--
-- Shelley stake extended ed25519 keys
--

-- | Shelley-era stake keys using extended ed25519 cryptographic keys.
--
-- They can be used for Shelley stake addresses and witnessing transactions
-- that use stake addresses.
--
-- These extended keys are used by HD wallets. So this type provides
-- interoperability with HD wallets. The ITN CLI also supported this key type.
--
-- The extended verification keys can be converted (via 'castVerificationKey')
-- to ordinary keys (i.e. 'VerificationKey' 'StakeKey') but this is /not/ the
-- case for the signing keys. The signing keys can be used to witness
-- transactions directly, with verification via their non-extended verification
-- key ('VerificationKey' 'StakeKey').
--
-- This is a type level tag, used with other interfaces like 'Key'.
data StakeExtendedKey

instance HasTypeProxy StakeExtendedKey where
  data AsType StakeExtendedKey = AsStakeExtendedKey
  proxyToAsType :: Proxy StakeExtendedKey -> AsType StakeExtendedKey
proxyToAsType Proxy StakeExtendedKey
_ = AsType StakeExtendedKey
AsStakeExtendedKey

instance Key StakeExtendedKey where
  newtype VerificationKey StakeExtendedKey
    = StakeExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
(VerificationKey StakeExtendedKey
 -> VerificationKey StakeExtendedKey -> Bool)
-> (VerificationKey StakeExtendedKey
    -> VerificationKey StakeExtendedKey -> Bool)
-> Eq (VerificationKey StakeExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
== :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
$c/= :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
/= :: VerificationKey StakeExtendedKey
-> VerificationKey StakeExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey StakeExtendedKey)
HasTypeProxy (VerificationKey StakeExtendedKey) =>
(VerificationKey StakeExtendedKey -> ByteString)
-> (AsType (VerificationKey StakeExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey StakeExtendedKey))
-> SerialiseAsCBOR (VerificationKey StakeExtendedKey)
AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey)
VerificationKey StakeExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey StakeExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey StakeExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey StakeExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakeExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey StakeExtendedKey -> ShowS
[VerificationKey StakeExtendedKey] -> ShowS
VerificationKey StakeExtendedKey -> String
(Int -> VerificationKey StakeExtendedKey -> ShowS)
-> (VerificationKey StakeExtendedKey -> String)
-> ([VerificationKey StakeExtendedKey] -> ShowS)
-> Show (VerificationKey StakeExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS
$cshow :: VerificationKey StakeExtendedKey -> String
show :: VerificationKey StakeExtendedKey -> String
$cshowList :: [VerificationKey StakeExtendedKey] -> ShowS
showList :: [VerificationKey StakeExtendedKey] -> ShowS
Show, String -> VerificationKey StakeExtendedKey
(String -> VerificationKey StakeExtendedKey)
-> IsString (VerificationKey StakeExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey StakeExtendedKey
fromString :: String -> VerificationKey StakeExtendedKey
IsString) via UsingRawBytesHex (VerificationKey StakeExtendedKey)

  newtype SigningKey StakeExtendedKey
    = StakeExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey StakeExtendedKey)
HasTypeProxy (SigningKey StakeExtendedKey) =>
(SigningKey StakeExtendedKey -> ByteString)
-> (AsType (SigningKey StakeExtendedKey)
    -> ByteString -> Either DecoderError (SigningKey StakeExtendedKey))
-> SerialiseAsCBOR (SigningKey StakeExtendedKey)
AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey)
SigningKey StakeExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey StakeExtendedKey -> ByteString
serialiseToCBOR :: SigningKey StakeExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey StakeExtendedKey)
-> ByteString -> Either DecoderError (SigningKey StakeExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey StakeExtendedKey -> ShowS
[SigningKey StakeExtendedKey] -> ShowS
SigningKey StakeExtendedKey -> String
(Int -> SigningKey StakeExtendedKey -> ShowS)
-> (SigningKey StakeExtendedKey -> String)
-> ([SigningKey StakeExtendedKey] -> ShowS)
-> Show (SigningKey StakeExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS
showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS
$cshow :: SigningKey StakeExtendedKey -> String
show :: SigningKey StakeExtendedKey -> String
$cshowList :: [SigningKey StakeExtendedKey] -> ShowS
showList :: [SigningKey StakeExtendedKey] -> ShowS
Show, String -> SigningKey StakeExtendedKey
(String -> SigningKey StakeExtendedKey)
-> IsString (SigningKey StakeExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey StakeExtendedKey
fromString :: 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
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word
deterministicSigningKeySeedSize AsType StakeExtendedKey
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
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey StakeExtendedKey
    -> Hash StakeExtendedKey
  verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey
verificationKeyHash (StakeExtendedVerificationKey XPub
vk) =
    KeyHash 'Staking -> Hash StakeExtendedKey
StakeExtendedKeyHash
      (KeyHash 'Staking -> Hash StakeExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'Staking)
-> Hash ADDRHASH XPub
-> Hash StakeExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'Staking
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash StakeExtendedKey)
-> Hash ADDRHASH XPub -> Hash StakeExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

instance ToCBOR (VerificationKey StakeExtendedKey) where
  toCBOR :: VerificationKey StakeExtendedKey -> Encoding
toCBOR (StakeExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey StakeExtendedKey))
-> (XPub -> Decoder s (VerificationKey StakeExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey StakeExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey StakeExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey StakeExtendedKey
-> Decoder s (VerificationKey StakeExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey StakeExtendedKey
 -> Decoder s (VerificationKey StakeExtendedKey))
-> (XPub -> VerificationKey StakeExtendedKey)
-> XPub
-> Decoder s (VerificationKey StakeExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey StakeExtendedKey) where
  toCBOR :: SigningKey StakeExtendedKey -> Encoding
toCBOR (StakeExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey StakeExtendedKey))
-> (XPrv -> Decoder s (SigningKey StakeExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey StakeExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey StakeExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey StakeExtendedKey
-> Decoder s (SigningKey StakeExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey StakeExtendedKey
 -> Decoder s (SigningKey StakeExtendedKey))
-> (XPrv -> SigningKey StakeExtendedKey)
-> XPrv
-> Decoder s (SigningKey StakeExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey StakeExtendedKey) where
  serialiseToRawBytes :: VerificationKey StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedVerificationKey XPub
xpub) =
    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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey StakeExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey StakeExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg))
      (Either String (VerificationKey StakeExtendedKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey StakeExtendedKey))
-> Either String (VerificationKey StakeExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPub -> VerificationKey StakeExtendedKey
StakeExtendedVerificationKey (XPub -> VerificationKey StakeExtendedKey)
-> Either String XPub
-> Either String (VerificationKey StakeExtendedKey)
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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey StakeExtendedKey)
-> Either SerialiseAsRawBytesError (SigningKey StakeExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg))
      (Either String (SigningKey StakeExtendedKey)
 -> Either SerialiseAsRawBytesError (SigningKey StakeExtendedKey))
-> Either String (SigningKey StakeExtendedKey)
-> Either SerialiseAsRawBytesError (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey (XPrv -> SigningKey StakeExtendedKey)
-> Either String XPrv
-> Either String (SigningKey StakeExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs

instance SerialiseAsBech32 (VerificationKey StakeExtendedKey) where
  bech32PrefixFor :: VerificationKey StakeExtendedKey -> Text
bech32PrefixFor VerificationKey StakeExtendedKey
_ = Text
"stake_xvk"
  bech32PrefixesPermitted :: AsType (VerificationKey StakeExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey StakeExtendedKey)
_ = [Text
"stake_xvk"]

instance SerialiseAsBech32 (SigningKey StakeExtendedKey) where
  bech32PrefixFor :: SigningKey StakeExtendedKey -> Text
bech32PrefixFor SigningKey StakeExtendedKey
_ = Text
"stake_xsk"
  bech32PrefixesPermitted :: AsType (SigningKey StakeExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey StakeExtendedKey)
_ = [Text
"stake_xsk"]

newtype instance Hash StakeExtendedKey
  = StakeExtendedKeyHash {Hash StakeExtendedKey -> KeyHash 'Staking
unStakeExtendedKeyHash :: Shelley.KeyHash Shelley.Staking}
  deriving stock (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
(Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> Eq (Hash StakeExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
== :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$c/= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
/= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
Eq, Eq (Hash StakeExtendedKey)
Eq (Hash StakeExtendedKey) =>
(Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool)
-> (Hash StakeExtendedKey
    -> Hash StakeExtendedKey -> Hash StakeExtendedKey)
-> (Hash StakeExtendedKey
    -> Hash StakeExtendedKey -> Hash StakeExtendedKey)
-> Ord (Hash StakeExtendedKey)
Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering
Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering
compare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering
$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
>= :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool
$cmax :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
max :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
$cmin :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
min :: Hash StakeExtendedKey
-> Hash StakeExtendedKey -> Hash StakeExtendedKey
Ord)
  deriving (Int -> Hash StakeExtendedKey -> ShowS
[Hash StakeExtendedKey] -> ShowS
Hash StakeExtendedKey -> String
(Int -> Hash StakeExtendedKey -> ShowS)
-> (Hash StakeExtendedKey -> String)
-> ([Hash StakeExtendedKey] -> ShowS)
-> Show (Hash StakeExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash StakeExtendedKey -> ShowS
showsPrec :: Int -> Hash StakeExtendedKey -> ShowS
$cshow :: Hash StakeExtendedKey -> String
show :: Hash StakeExtendedKey -> String
$cshowList :: [Hash StakeExtendedKey] -> ShowS
showList :: [Hash StakeExtendedKey] -> ShowS
Show, String -> Hash StakeExtendedKey
(String -> Hash StakeExtendedKey)
-> IsString (Hash StakeExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash StakeExtendedKey
fromString :: String -> Hash StakeExtendedKey
IsString) via UsingRawBytesHex (Hash StakeExtendedKey)
  deriving (Typeable (Hash StakeExtendedKey)
Typeable (Hash StakeExtendedKey) =>
(Hash StakeExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash StakeExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash StakeExtendedKey] -> Size)
-> ToCBOR (Hash StakeExtendedKey)
Hash StakeExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash StakeExtendedKey -> Encoding
toCBOR :: Hash StakeExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakeExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakeExtendedKey] -> Size
ToCBOR, Typeable (Hash StakeExtendedKey)
Typeable (Hash StakeExtendedKey) =>
(forall s. Decoder s (Hash StakeExtendedKey))
-> (Proxy (Hash StakeExtendedKey) -> Text)
-> FromCBOR (Hash StakeExtendedKey)
Proxy (Hash StakeExtendedKey) -> Text
forall s. Decoder s (Hash StakeExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash StakeExtendedKey)
fromCBOR :: forall s. Decoder s (Hash StakeExtendedKey)
$clabel :: Proxy (Hash StakeExtendedKey) -> Text
label :: Proxy (Hash StakeExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash StakeExtendedKey)
  deriving anyclass HasTypeProxy (Hash StakeExtendedKey)
HasTypeProxy (Hash StakeExtendedKey) =>
(Hash StakeExtendedKey -> ByteString)
-> (AsType (Hash StakeExtendedKey)
    -> ByteString -> Either DecoderError (Hash StakeExtendedKey))
-> SerialiseAsCBOR (Hash StakeExtendedKey)
AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey)
Hash StakeExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash StakeExtendedKey -> ByteString
serialiseToCBOR :: Hash StakeExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey)
deserialiseFromCBOR :: AsType (Hash StakeExtendedKey)
-> ByteString -> Either DecoderError (Hash StakeExtendedKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash StakeExtendedKey) where
  serialiseToRawBytes :: Hash StakeExtendedKey -> ByteString
serialiseToRawBytes (StakeExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash StakeExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash StakeExtendedKey)
deserialiseFromRawBytes (AsHash AsType StakeExtendedKey
R:AsTypeStakeExtendedKey
AsStakeExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash StakeExtendedKey)
-> Either SerialiseAsRawBytesError (Hash StakeExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakeExtendedKey") (Maybe (Hash StakeExtendedKey)
 -> Either SerialiseAsRawBytesError (Hash StakeExtendedKey))
-> Maybe (Hash StakeExtendedKey)
-> Either SerialiseAsRawBytesError (Hash StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Staking -> Hash StakeExtendedKey
StakeExtendedKeyHash (KeyHash 'Staking -> Hash StakeExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash StakeExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash StakeExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash StakeExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
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 -> VerificationKey StakeKey
StakeVerificationKey
      (VKey 'Staking -> VerificationKey StakeKey)
-> (XPub -> VKey 'Staking) -> XPub -> VerificationKey StakeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Staking
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'Staking)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'Staking
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey StakeKey)
-> XPub -> VerificationKey StakeKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley key sizes do not match!"

--
-- Genesis keys
--

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)
    deriving stock VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
(VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool)
-> (VerificationKey GenesisKey
    -> VerificationKey GenesisKey -> Bool)
-> Eq (VerificationKey GenesisKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
== :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
$c/= :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
/= :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool
Eq
    deriving (Int -> VerificationKey GenesisKey -> ShowS
[VerificationKey GenesisKey] -> ShowS
VerificationKey GenesisKey -> String
(Int -> VerificationKey GenesisKey -> ShowS)
-> (VerificationKey GenesisKey -> String)
-> ([VerificationKey GenesisKey] -> ShowS)
-> Show (VerificationKey GenesisKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey GenesisKey -> ShowS
showsPrec :: Int -> VerificationKey GenesisKey -> ShowS
$cshow :: VerificationKey GenesisKey -> String
show :: VerificationKey GenesisKey -> String
$cshowList :: [VerificationKey GenesisKey] -> ShowS
showList :: [VerificationKey GenesisKey] -> ShowS
Show, String -> VerificationKey GenesisKey
(String -> VerificationKey GenesisKey)
-> IsString (VerificationKey GenesisKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey GenesisKey
fromString :: String -> VerificationKey GenesisKey
IsString) via UsingRawBytesHex (VerificationKey GenesisKey)
    deriving newtype (Typeable (VerificationKey GenesisKey)
Typeable (VerificationKey GenesisKey) =>
(VerificationKey GenesisKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey GenesisKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey GenesisKey] -> Size)
-> ToCBOR (VerificationKey GenesisKey)
VerificationKey GenesisKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VerificationKey GenesisKey -> Encoding
toCBOR :: VerificationKey GenesisKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisKey] -> Size
ToCBOR, Typeable (VerificationKey GenesisKey)
Typeable (VerificationKey GenesisKey) =>
(forall s. Decoder s (VerificationKey GenesisKey))
-> (Proxy (VerificationKey GenesisKey) -> Text)
-> FromCBOR (VerificationKey GenesisKey)
Proxy (VerificationKey GenesisKey) -> Text
forall s. Decoder s (VerificationKey GenesisKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisKey)
fromCBOR :: forall s. Decoder s (VerificationKey GenesisKey)
$clabel :: Proxy (VerificationKey GenesisKey) -> Text
label :: Proxy (VerificationKey GenesisKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey GenesisKey)
HasTypeProxy (VerificationKey GenesisKey) =>
(VerificationKey GenesisKey -> ByteString)
-> (AsType (VerificationKey GenesisKey)
    -> ByteString -> Either DecoderError (VerificationKey GenesisKey))
-> SerialiseAsCBOR (VerificationKey GenesisKey)
AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey)
VerificationKey GenesisKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey GenesisKey -> ByteString
serialiseToCBOR :: VerificationKey GenesisKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey)
deserialiseFromCBOR :: AsType (VerificationKey GenesisKey)
-> ByteString -> Either DecoderError (VerificationKey GenesisKey)
SerialiseAsCBOR

  newtype SigningKey GenesisKey
    = GenesisSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey GenesisKey -> ShowS
[SigningKey GenesisKey] -> ShowS
SigningKey GenesisKey -> String
(Int -> SigningKey GenesisKey -> ShowS)
-> (SigningKey GenesisKey -> String)
-> ([SigningKey GenesisKey] -> ShowS)
-> Show (SigningKey GenesisKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey GenesisKey -> ShowS
showsPrec :: Int -> SigningKey GenesisKey -> ShowS
$cshow :: SigningKey GenesisKey -> String
show :: SigningKey GenesisKey -> String
$cshowList :: [SigningKey GenesisKey] -> ShowS
showList :: [SigningKey GenesisKey] -> ShowS
Show, String -> SigningKey GenesisKey
(String -> SigningKey GenesisKey)
-> IsString (SigningKey GenesisKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey GenesisKey
fromString :: String -> SigningKey GenesisKey
IsString) via UsingRawBytesHex (SigningKey GenesisKey)
    deriving newtype (Typeable (SigningKey GenesisKey)
Typeable (SigningKey GenesisKey) =>
(SigningKey GenesisKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey GenesisKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey GenesisKey] -> Size)
-> ToCBOR (SigningKey GenesisKey)
SigningKey GenesisKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SigningKey GenesisKey -> Encoding
toCBOR :: SigningKey GenesisKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisKey] -> Size
ToCBOR, Typeable (SigningKey GenesisKey)
Typeable (SigningKey GenesisKey) =>
(forall s. Decoder s (SigningKey GenesisKey))
-> (Proxy (SigningKey GenesisKey) -> Text)
-> FromCBOR (SigningKey GenesisKey)
Proxy (SigningKey GenesisKey) -> Text
forall s. Decoder s (SigningKey GenesisKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisKey)
fromCBOR :: forall s. Decoder s (SigningKey GenesisKey)
$clabel :: Proxy (SigningKey GenesisKey) -> Text
label :: Proxy (SigningKey GenesisKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey GenesisKey)
HasTypeProxy (SigningKey GenesisKey) =>
(SigningKey GenesisKey -> ByteString)
-> (AsType (SigningKey GenesisKey)
    -> ByteString -> Either DecoderError (SigningKey GenesisKey))
-> SerialiseAsCBOR (SigningKey GenesisKey)
AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey)
SigningKey GenesisKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey GenesisKey -> ByteString
serialiseToCBOR :: SigningKey GenesisKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey)
deserialiseFromCBOR :: AsType (SigningKey GenesisKey)
-> ByteString -> Either DecoderError (SigningKey GenesisKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType GenesisKey -> Crypto.Seed -> SigningKey GenesisKey
  deterministicSigningKey :: AsType GenesisKey -> Seed -> SigningKey GenesisKey
deterministicSigningKey AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey GenesisKey
GenesisSigningKey (Seed -> SignKeyDSIGN DSIGN
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 =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey
  getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey
getVerificationKey (GenesisSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'Genesis -> VerificationKey GenesisKey
GenesisVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Genesis
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey
  verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey
verificationKeyHash (GenesisVerificationKey VKey 'Genesis
vkey) =
    KeyHash 'Genesis -> Hash GenesisKey
GenesisKeyHash (VKey 'Genesis -> KeyHash 'Genesis
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'Genesis
vkey)

instance SerialiseAsRawBytes (VerificationKey GenesisKey) where
  serialiseToRawBytes :: VerificationKey GenesisKey -> ByteString
serialiseToRawBytes (GenesisVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey GenesisKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey GenesisKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey GenesisKey)
-> Either SerialiseAsRawBytesError (VerificationKey GenesisKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisKey") (Maybe (VerificationKey GenesisKey)
 -> Either SerialiseAsRawBytesError (VerificationKey GenesisKey))
-> Maybe (VerificationKey GenesisKey)
-> Either SerialiseAsRawBytesError (VerificationKey GenesisKey)
forall a b. (a -> b) -> a -> b
$
      VKey 'Genesis -> VerificationKey GenesisKey
GenesisVerificationKey (VKey 'Genesis -> VerificationKey GenesisKey)
-> (VerKeyDSIGN DSIGN -> VKey 'Genesis)
-> VerKeyDSIGN DSIGN
-> VerificationKey GenesisKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Genesis
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey GenesisKey)
-> Maybe (VerKeyDSIGN DSIGN) -> Maybe (VerificationKey GenesisKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey GenesisKey) where
  serialiseToRawBytes :: SigningKey GenesisKey -> ByteString
serialiseToRawBytes (GenesisSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey GenesisKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (SigningKey GenesisKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey GenesisKey") (Maybe (SigningKey GenesisKey)
 -> Either SerialiseAsRawBytesError (SigningKey GenesisKey))
-> Maybe (SigningKey GenesisKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisKey)
forall a b. (a -> b) -> a -> b
$
      SignKeyDSIGN DSIGN -> SigningKey GenesisKey
GenesisSigningKey (SignKeyDSIGN DSIGN -> SigningKey GenesisKey)
-> Maybe (SignKeyDSIGN DSIGN) -> Maybe (SigningKey GenesisKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs

newtype instance Hash GenesisKey
  = GenesisKeyHash {Hash GenesisKey -> KeyHash 'Genesis
unGenesisKeyHash :: Shelley.KeyHash Shelley.Genesis}
  deriving stock (Hash GenesisKey -> Hash GenesisKey -> Bool
(Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> Eq (Hash GenesisKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash GenesisKey -> Hash GenesisKey -> Bool
== :: Hash GenesisKey -> Hash GenesisKey -> Bool
$c/= :: Hash GenesisKey -> Hash GenesisKey -> Bool
/= :: Hash GenesisKey -> Hash GenesisKey -> Bool
Eq, Eq (Hash GenesisKey)
Eq (Hash GenesisKey) =>
(Hash GenesisKey -> Hash GenesisKey -> Ordering)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Bool)
-> (Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey)
-> (Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey)
-> Ord (Hash GenesisKey)
Hash GenesisKey -> Hash GenesisKey -> Bool
Hash GenesisKey -> Hash GenesisKey -> Ordering
Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash GenesisKey -> Hash GenesisKey -> Ordering
compare :: Hash GenesisKey -> Hash GenesisKey -> Ordering
$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
>= :: Hash GenesisKey -> Hash GenesisKey -> Bool
$cmax :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
max :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
$cmin :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
min :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey
Ord)
  deriving (Int -> Hash GenesisKey -> ShowS
[Hash GenesisKey] -> ShowS
Hash GenesisKey -> String
(Int -> Hash GenesisKey -> ShowS)
-> (Hash GenesisKey -> String)
-> ([Hash GenesisKey] -> ShowS)
-> Show (Hash GenesisKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash GenesisKey -> ShowS
showsPrec :: Int -> Hash GenesisKey -> ShowS
$cshow :: Hash GenesisKey -> String
show :: Hash GenesisKey -> String
$cshowList :: [Hash GenesisKey] -> ShowS
showList :: [Hash GenesisKey] -> ShowS
Show, String -> Hash GenesisKey
(String -> Hash GenesisKey) -> IsString (Hash GenesisKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash GenesisKey
fromString :: String -> Hash GenesisKey
IsString) via UsingRawBytesHex (Hash GenesisKey)
  deriving (Typeable (Hash GenesisKey)
Typeable (Hash GenesisKey) =>
(Hash GenesisKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash GenesisKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash GenesisKey] -> Size)
-> ToCBOR (Hash GenesisKey)
Hash GenesisKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash GenesisKey -> Encoding
toCBOR :: Hash GenesisKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisKey] -> Size
ToCBOR, Typeable (Hash GenesisKey)
Typeable (Hash GenesisKey) =>
(forall s. Decoder s (Hash GenesisKey))
-> (Proxy (Hash GenesisKey) -> Text) -> FromCBOR (Hash GenesisKey)
Proxy (Hash GenesisKey) -> Text
forall s. Decoder s (Hash GenesisKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash GenesisKey)
fromCBOR :: forall s. Decoder s (Hash GenesisKey)
$clabel :: Proxy (Hash GenesisKey) -> Text
label :: Proxy (Hash GenesisKey) -> Text
FromCBOR) via UsingRawBytes (Hash GenesisKey)
  deriving (ToJSONKeyFunction [Hash GenesisKey]
ToJSONKeyFunction (Hash GenesisKey)
ToJSONKeyFunction (Hash GenesisKey)
-> ToJSONKeyFunction [Hash GenesisKey]
-> ToJSONKey (Hash GenesisKey)
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
$ctoJSONKey :: ToJSONKeyFunction (Hash GenesisKey)
toJSONKey :: ToJSONKeyFunction (Hash GenesisKey)
$ctoJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey]
toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey]
ToJSONKey, [Hash GenesisKey] -> Value
[Hash GenesisKey] -> Encoding
Hash GenesisKey -> Bool
Hash GenesisKey -> Value
Hash GenesisKey -> Encoding
(Hash GenesisKey -> Value)
-> (Hash GenesisKey -> Encoding)
-> ([Hash GenesisKey] -> Value)
-> ([Hash GenesisKey] -> Encoding)
-> (Hash GenesisKey -> Bool)
-> ToJSON (Hash GenesisKey)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Hash GenesisKey -> Value
toJSON :: Hash GenesisKey -> Value
$ctoEncoding :: Hash GenesisKey -> Encoding
toEncoding :: Hash GenesisKey -> Encoding
$ctoJSONList :: [Hash GenesisKey] -> Value
toJSONList :: [Hash GenesisKey] -> Value
$ctoEncodingList :: [Hash GenesisKey] -> Encoding
toEncodingList :: [Hash GenesisKey] -> Encoding
$comitField :: Hash GenesisKey -> Bool
omitField :: Hash GenesisKey -> Bool
ToJSON, Maybe (Hash GenesisKey)
Value -> Parser [Hash GenesisKey]
Value -> Parser (Hash GenesisKey)
(Value -> Parser (Hash GenesisKey))
-> (Value -> Parser [Hash GenesisKey])
-> Maybe (Hash GenesisKey)
-> FromJSON (Hash GenesisKey)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser (Hash GenesisKey)
parseJSON :: Value -> Parser (Hash GenesisKey)
$cparseJSONList :: Value -> Parser [Hash GenesisKey]
parseJSONList :: Value -> Parser [Hash GenesisKey]
$comittedField :: Maybe (Hash GenesisKey)
omittedField :: Maybe (Hash GenesisKey)
FromJSON) via UsingRawBytesHex (Hash GenesisKey)
  deriving anyclass HasTypeProxy (Hash GenesisKey)
HasTypeProxy (Hash GenesisKey) =>
(Hash GenesisKey -> ByteString)
-> (AsType (Hash GenesisKey)
    -> ByteString -> Either DecoderError (Hash GenesisKey))
-> SerialiseAsCBOR (Hash GenesisKey)
AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey)
Hash GenesisKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash GenesisKey -> ByteString
serialiseToCBOR :: Hash GenesisKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey)
deserialiseFromCBOR :: AsType (Hash GenesisKey)
-> ByteString -> Either DecoderError (Hash GenesisKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash GenesisKey) where
  serialiseToRawBytes :: Hash GenesisKey -> ByteString
serialiseToRawBytes (GenesisKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash GenesisKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash GenesisKey)
deserialiseFromRawBytes (AsHash AsType GenesisKey
R:AsTypeGenesisKey
AsGenesisKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash GenesisKey)
-> Either SerialiseAsRawBytesError (Hash GenesisKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisKey") (Maybe (Hash GenesisKey)
 -> Either SerialiseAsRawBytesError (Hash GenesisKey))
-> Maybe (Hash GenesisKey)
-> Either SerialiseAsRawBytesError (Hash GenesisKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Genesis -> Hash GenesisKey
GenesisKeyHash (KeyHash 'Genesis -> Hash GenesisKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Genesis)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash GenesisKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Genesis
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash GenesisKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash GenesisKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey GenesisKey) where
  textEnvelopeType :: AsType (VerificationKey GenesisKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisKey)
_ =
    TextEnvelopeType
"GenesisVerificationKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey GenesisKey) where
  textEnvelopeType :: AsType (SigningKey GenesisKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisKey)
_ =
    TextEnvelopeType
"GenesisSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance CastVerificationKeyRole GenesisKey PaymentKey where
  castVerificationKey :: VerificationKey GenesisKey -> VerificationKey PaymentKey
castVerificationKey (GenesisVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VKey 'Payment -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey VerKeyDSIGN DSIGN
vk)

--
-- Constitutional Committee Hot Keys
--

data CommitteeHotKey

instance HasTypeProxy CommitteeHotKey where
  data AsType CommitteeHotKey = AsCommitteeHotKey
  proxyToAsType :: Proxy CommitteeHotKey -> AsType CommitteeHotKey
proxyToAsType Proxy CommitteeHotKey
_ = AsType CommitteeHotKey
AsCommitteeHotKey

instance Key CommitteeHotKey where
  newtype VerificationKey CommitteeHotKey
    = CommitteeHotVerificationKey (Shelley.VKey Shelley.HotCommitteeRole)
    deriving stock VerificationKey CommitteeHotKey
-> VerificationKey CommitteeHotKey -> Bool
(VerificationKey CommitteeHotKey
 -> VerificationKey CommitteeHotKey -> Bool)
-> (VerificationKey CommitteeHotKey
    -> VerificationKey CommitteeHotKey -> Bool)
-> Eq (VerificationKey CommitteeHotKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey CommitteeHotKey
-> VerificationKey CommitteeHotKey -> Bool
== :: VerificationKey CommitteeHotKey
-> VerificationKey CommitteeHotKey -> Bool
$c/= :: VerificationKey CommitteeHotKey
-> VerificationKey CommitteeHotKey -> Bool
/= :: VerificationKey CommitteeHotKey
-> VerificationKey CommitteeHotKey -> Bool
Eq
    deriving (Int -> VerificationKey CommitteeHotKey -> ShowS
[VerificationKey CommitteeHotKey] -> ShowS
VerificationKey CommitteeHotKey -> String
(Int -> VerificationKey CommitteeHotKey -> ShowS)
-> (VerificationKey CommitteeHotKey -> String)
-> ([VerificationKey CommitteeHotKey] -> ShowS)
-> Show (VerificationKey CommitteeHotKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey CommitteeHotKey -> ShowS
showsPrec :: Int -> VerificationKey CommitteeHotKey -> ShowS
$cshow :: VerificationKey CommitteeHotKey -> String
show :: VerificationKey CommitteeHotKey -> String
$cshowList :: [VerificationKey CommitteeHotKey] -> ShowS
showList :: [VerificationKey CommitteeHotKey] -> ShowS
Show, String -> VerificationKey CommitteeHotKey
(String -> VerificationKey CommitteeHotKey)
-> IsString (VerificationKey CommitteeHotKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey CommitteeHotKey
fromString :: String -> VerificationKey CommitteeHotKey
IsString) via UsingRawBytesHex (VerificationKey CommitteeHotKey)
    deriving newtype (Typeable (VerificationKey CommitteeHotKey)
Typeable (VerificationKey CommitteeHotKey) =>
(VerificationKey CommitteeHotKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey CommitteeHotKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey CommitteeHotKey] -> Size)
-> ToCBOR (VerificationKey CommitteeHotKey)
VerificationKey CommitteeHotKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey CommitteeHotKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey CommitteeHotKey) -> 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
$ctoCBOR :: VerificationKey CommitteeHotKey -> Encoding
toCBOR :: VerificationKey CommitteeHotKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey CommitteeHotKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey CommitteeHotKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey CommitteeHotKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey CommitteeHotKey] -> Size
ToCBOR, Typeable (VerificationKey CommitteeHotKey)
Typeable (VerificationKey CommitteeHotKey) =>
(forall s. Decoder s (VerificationKey CommitteeHotKey))
-> (Proxy (VerificationKey CommitteeHotKey) -> Text)
-> FromCBOR (VerificationKey CommitteeHotKey)
Proxy (VerificationKey CommitteeHotKey) -> Text
forall s. Decoder s (VerificationKey CommitteeHotKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey CommitteeHotKey)
fromCBOR :: forall s. Decoder s (VerificationKey CommitteeHotKey)
$clabel :: Proxy (VerificationKey CommitteeHotKey) -> Text
label :: Proxy (VerificationKey CommitteeHotKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey CommitteeHotKey)
HasTypeProxy (VerificationKey CommitteeHotKey) =>
(VerificationKey CommitteeHotKey -> ByteString)
-> (AsType (VerificationKey CommitteeHotKey)
    -> ByteString
    -> Either DecoderError (VerificationKey CommitteeHotKey))
-> SerialiseAsCBOR (VerificationKey CommitteeHotKey)
AsType (VerificationKey CommitteeHotKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeHotKey)
VerificationKey CommitteeHotKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey CommitteeHotKey -> ByteString
serialiseToCBOR :: VerificationKey CommitteeHotKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey CommitteeHotKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeHotKey)
deserialiseFromCBOR :: AsType (VerificationKey CommitteeHotKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeHotKey)
SerialiseAsCBOR

  newtype SigningKey CommitteeHotKey
    = CommitteeHotSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey CommitteeHotKey -> ShowS
[SigningKey CommitteeHotKey] -> ShowS
SigningKey CommitteeHotKey -> String
(Int -> SigningKey CommitteeHotKey -> ShowS)
-> (SigningKey CommitteeHotKey -> String)
-> ([SigningKey CommitteeHotKey] -> ShowS)
-> Show (SigningKey CommitteeHotKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey CommitteeHotKey -> ShowS
showsPrec :: Int -> SigningKey CommitteeHotKey -> ShowS
$cshow :: SigningKey CommitteeHotKey -> String
show :: SigningKey CommitteeHotKey -> String
$cshowList :: [SigningKey CommitteeHotKey] -> ShowS
showList :: [SigningKey CommitteeHotKey] -> ShowS
Show, String -> SigningKey CommitteeHotKey
(String -> SigningKey CommitteeHotKey)
-> IsString (SigningKey CommitteeHotKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey CommitteeHotKey
fromString :: String -> SigningKey CommitteeHotKey
IsString) via UsingRawBytesHex (SigningKey CommitteeHotKey)
    deriving newtype (Typeable (SigningKey CommitteeHotKey)
Typeable (SigningKey CommitteeHotKey) =>
(SigningKey CommitteeHotKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey CommitteeHotKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey CommitteeHotKey] -> Size)
-> ToCBOR (SigningKey CommitteeHotKey)
SigningKey CommitteeHotKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey CommitteeHotKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey CommitteeHotKey) -> 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
$ctoCBOR :: SigningKey CommitteeHotKey -> Encoding
toCBOR :: SigningKey CommitteeHotKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey CommitteeHotKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey CommitteeHotKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey CommitteeHotKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey CommitteeHotKey] -> Size
ToCBOR, Typeable (SigningKey CommitteeHotKey)
Typeable (SigningKey CommitteeHotKey) =>
(forall s. Decoder s (SigningKey CommitteeHotKey))
-> (Proxy (SigningKey CommitteeHotKey) -> Text)
-> FromCBOR (SigningKey CommitteeHotKey)
Proxy (SigningKey CommitteeHotKey) -> Text
forall s. Decoder s (SigningKey CommitteeHotKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey CommitteeHotKey)
fromCBOR :: forall s. Decoder s (SigningKey CommitteeHotKey)
$clabel :: Proxy (SigningKey CommitteeHotKey) -> Text
label :: Proxy (SigningKey CommitteeHotKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey CommitteeHotKey)
HasTypeProxy (SigningKey CommitteeHotKey) =>
(SigningKey CommitteeHotKey -> ByteString)
-> (AsType (SigningKey CommitteeHotKey)
    -> ByteString -> Either DecoderError (SigningKey CommitteeHotKey))
-> SerialiseAsCBOR (SigningKey CommitteeHotKey)
AsType (SigningKey CommitteeHotKey)
-> ByteString -> Either DecoderError (SigningKey CommitteeHotKey)
SigningKey CommitteeHotKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey CommitteeHotKey -> ByteString
serialiseToCBOR :: SigningKey CommitteeHotKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey CommitteeHotKey)
-> ByteString -> Either DecoderError (SigningKey CommitteeHotKey)
deserialiseFromCBOR :: AsType (SigningKey CommitteeHotKey)
-> ByteString -> Either DecoderError (SigningKey CommitteeHotKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType CommitteeHotKey -> Crypto.Seed -> SigningKey CommitteeHotKey
  deterministicSigningKey :: AsType CommitteeHotKey -> Seed -> SigningKey CommitteeHotKey
deterministicSigningKey AsType CommitteeHotKey
R:AsTypeCommitteeHotKey
AsCommitteeHotKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey CommitteeHotKey
CommitteeHotSigningKey (Seed -> SignKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)

  deterministicSigningKeySeedSize :: AsType CommitteeHotKey -> Word
  deterministicSigningKeySeedSize :: AsType CommitteeHotKey -> Word
deterministicSigningKeySeedSize AsType CommitteeHotKey
R:AsTypeCommitteeHotKey
AsCommitteeHotKey =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey CommitteeHotKey -> VerificationKey CommitteeHotKey
  getVerificationKey :: SigningKey CommitteeHotKey -> VerificationKey CommitteeHotKey
getVerificationKey (CommitteeHotSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'HotCommitteeRole -> VerificationKey CommitteeHotKey
CommitteeHotVerificationKey (VerKeyDSIGN DSIGN -> VKey 'HotCommitteeRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey CommitteeHotKey -> Hash CommitteeHotKey
  verificationKeyHash :: VerificationKey CommitteeHotKey -> Hash CommitteeHotKey
verificationKeyHash (CommitteeHotVerificationKey VKey 'HotCommitteeRole
vkey) =
    KeyHash 'HotCommitteeRole -> Hash CommitteeHotKey
CommitteeHotKeyHash (VKey 'HotCommitteeRole -> KeyHash 'HotCommitteeRole
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'HotCommitteeRole
vkey)

instance SerialiseAsRawBytes (VerificationKey CommitteeHotKey) where
  serialiseToRawBytes :: VerificationKey CommitteeHotKey -> ByteString
serialiseToRawBytes (CommitteeHotVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey CommitteeHotKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeHotKey)
deserialiseFromRawBytes (AsVerificationKey AsType CommitteeHotKey
R:AsTypeCommitteeHotKey
AsCommitteeHotKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey CommitteeHotKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeHotKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey Constitutional Committee Hot Key")
      (Maybe (VerificationKey CommitteeHotKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey CommitteeHotKey))
-> Maybe (VerificationKey CommitteeHotKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeHotKey)
forall a b. (a -> b) -> a -> b
$ VKey 'HotCommitteeRole -> VerificationKey CommitteeHotKey
CommitteeHotVerificationKey (VKey 'HotCommitteeRole -> VerificationKey CommitteeHotKey)
-> (VerKeyDSIGN DSIGN -> VKey 'HotCommitteeRole)
-> VerKeyDSIGN DSIGN
-> VerificationKey CommitteeHotKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'HotCommitteeRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey CommitteeHotKey)
-> Maybe (VerKeyDSIGN DSIGN)
-> Maybe (VerificationKey CommitteeHotKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey CommitteeHotKey) where
  serialiseToRawBytes :: SigningKey CommitteeHotKey -> ByteString
serialiseToRawBytes (CommitteeHotSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey CommitteeHotKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey CommitteeHotKey)
deserialiseFromRawBytes (AsSigningKey AsType CommitteeHotKey
R:AsTypeCommitteeHotKey
AsCommitteeHotKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (SigningKey CommitteeHotKey)
-> Either SerialiseAsRawBytesError (SigningKey CommitteeHotKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey Constitutional Committee Hot Key")
      (Maybe (SigningKey CommitteeHotKey)
 -> Either SerialiseAsRawBytesError (SigningKey CommitteeHotKey))
-> Maybe (SigningKey CommitteeHotKey)
-> Either SerialiseAsRawBytesError (SigningKey CommitteeHotKey)
forall a b. (a -> b) -> a -> b
$ SignKeyDSIGN DSIGN -> SigningKey CommitteeHotKey
CommitteeHotSigningKey (SignKeyDSIGN DSIGN -> SigningKey CommitteeHotKey)
-> Maybe (SignKeyDSIGN DSIGN) -> Maybe (SigningKey CommitteeHotKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs

newtype instance Hash CommitteeHotKey
  = CommitteeHotKeyHash
  {Hash CommitteeHotKey -> KeyHash 'HotCommitteeRole
unCommitteeHotKeyHash :: Shelley.KeyHash Shelley.HotCommitteeRole}
  deriving stock (Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
(Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool)
-> (Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool)
-> Eq (Hash CommitteeHotKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
== :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
$c/= :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
/= :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
Eq, Eq (Hash CommitteeHotKey)
Eq (Hash CommitteeHotKey) =>
(Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering)
-> (Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool)
-> (Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool)
-> (Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool)
-> (Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool)
-> (Hash CommitteeHotKey
    -> Hash CommitteeHotKey -> Hash CommitteeHotKey)
-> (Hash CommitteeHotKey
    -> Hash CommitteeHotKey -> Hash CommitteeHotKey)
-> Ord (Hash CommitteeHotKey)
Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering
Hash CommitteeHotKey
-> Hash CommitteeHotKey -> Hash CommitteeHotKey
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
$ccompare :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering
compare :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering
$c< :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
< :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
$c<= :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
<= :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
$c> :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
> :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
$c>= :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
>= :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool
$cmax :: Hash CommitteeHotKey
-> Hash CommitteeHotKey -> Hash CommitteeHotKey
max :: Hash CommitteeHotKey
-> Hash CommitteeHotKey -> Hash CommitteeHotKey
$cmin :: Hash CommitteeHotKey
-> Hash CommitteeHotKey -> Hash CommitteeHotKey
min :: Hash CommitteeHotKey
-> Hash CommitteeHotKey -> Hash CommitteeHotKey
Ord)
  deriving (Int -> Hash CommitteeHotKey -> ShowS
[Hash CommitteeHotKey] -> ShowS
Hash CommitteeHotKey -> String
(Int -> Hash CommitteeHotKey -> ShowS)
-> (Hash CommitteeHotKey -> String)
-> ([Hash CommitteeHotKey] -> ShowS)
-> Show (Hash CommitteeHotKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash CommitteeHotKey -> ShowS
showsPrec :: Int -> Hash CommitteeHotKey -> ShowS
$cshow :: Hash CommitteeHotKey -> String
show :: Hash CommitteeHotKey -> String
$cshowList :: [Hash CommitteeHotKey] -> ShowS
showList :: [Hash CommitteeHotKey] -> ShowS
Show, String -> Hash CommitteeHotKey
(String -> Hash CommitteeHotKey) -> IsString (Hash CommitteeHotKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash CommitteeHotKey
fromString :: String -> Hash CommitteeHotKey
IsString) via UsingRawBytesHex (Hash CommitteeHotKey)
  deriving (Typeable (Hash CommitteeHotKey)
Typeable (Hash CommitteeHotKey) =>
(Hash CommitteeHotKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash CommitteeHotKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash CommitteeHotKey] -> Size)
-> ToCBOR (Hash CommitteeHotKey)
Hash CommitteeHotKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeHotKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeHotKey) -> 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
$ctoCBOR :: Hash CommitteeHotKey -> Encoding
toCBOR :: Hash CommitteeHotKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeHotKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeHotKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeHotKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeHotKey] -> Size
ToCBOR, Typeable (Hash CommitteeHotKey)
Typeable (Hash CommitteeHotKey) =>
(forall s. Decoder s (Hash CommitteeHotKey))
-> (Proxy (Hash CommitteeHotKey) -> Text)
-> FromCBOR (Hash CommitteeHotKey)
Proxy (Hash CommitteeHotKey) -> Text
forall s. Decoder s (Hash CommitteeHotKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash CommitteeHotKey)
fromCBOR :: forall s. Decoder s (Hash CommitteeHotKey)
$clabel :: Proxy (Hash CommitteeHotKey) -> Text
label :: Proxy (Hash CommitteeHotKey) -> Text
FromCBOR) via UsingRawBytes (Hash CommitteeHotKey)
  deriving anyclass HasTypeProxy (Hash CommitteeHotKey)
HasTypeProxy (Hash CommitteeHotKey) =>
(Hash CommitteeHotKey -> ByteString)
-> (AsType (Hash CommitteeHotKey)
    -> ByteString -> Either DecoderError (Hash CommitteeHotKey))
-> SerialiseAsCBOR (Hash CommitteeHotKey)
AsType (Hash CommitteeHotKey)
-> ByteString -> Either DecoderError (Hash CommitteeHotKey)
Hash CommitteeHotKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash CommitteeHotKey -> ByteString
serialiseToCBOR :: Hash CommitteeHotKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash CommitteeHotKey)
-> ByteString -> Either DecoderError (Hash CommitteeHotKey)
deserialiseFromCBOR :: AsType (Hash CommitteeHotKey)
-> ByteString -> Either DecoderError (Hash CommitteeHotKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash CommitteeHotKey) where
  serialiseToRawBytes :: Hash CommitteeHotKey -> ByteString
serialiseToRawBytes (CommitteeHotKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash CommitteeHotKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash CommitteeHotKey)
deserialiseFromRawBytes (AsHash AsType CommitteeHotKey
R:AsTypeCommitteeHotKey
AsCommitteeHotKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash CommitteeHotKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeHotKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash Constitutional Committee Hot Key")
      (Maybe (Hash CommitteeHotKey)
 -> Either SerialiseAsRawBytesError (Hash CommitteeHotKey))
-> Maybe (Hash CommitteeHotKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeHotKey)
forall a b. (a -> b) -> a -> b
$ KeyHash 'HotCommitteeRole -> Hash CommitteeHotKey
CommitteeHotKeyHash (KeyHash 'HotCommitteeRole -> Hash CommitteeHotKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'HotCommitteeRole)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash CommitteeHotKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'HotCommitteeRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash CommitteeHotKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash CommitteeHotKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey CommitteeHotKey) where
  textEnvelopeType :: AsType (VerificationKey CommitteeHotKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey CommitteeHotKey)
_ =
    TextEnvelopeType
"ConstitutionalCommitteeHotVerificationKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey CommitteeHotKey) where
  textEnvelopeType :: AsType (SigningKey CommitteeHotKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey CommitteeHotKey)
_ =
    TextEnvelopeType
"ConstitutionalCommitteeHotSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance CastVerificationKeyRole CommitteeHotKey PaymentKey where
  castVerificationKey :: VerificationKey CommitteeHotKey -> VerificationKey PaymentKey
castVerificationKey (CommitteeHotVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VKey 'Payment -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey VerKeyDSIGN DSIGN
vk)

instance SerialiseAsBech32 (Hash CommitteeHotKey) where
  bech32PrefixFor :: Hash CommitteeHotKey -> Text
bech32PrefixFor Hash CommitteeHotKey
_ = Text
"cc_hot"
  bech32PrefixesPermitted :: AsType (Hash CommitteeHotKey) -> [Text]
bech32PrefixesPermitted AsType (Hash CommitteeHotKey)
_ = [Text
"cc_hot"]

instance SerialiseAsBech32 (VerificationKey CommitteeHotKey) where
  bech32PrefixFor :: VerificationKey CommitteeHotKey -> Text
bech32PrefixFor VerificationKey CommitteeHotKey
_ = Text
"cc_hot_vk"
  bech32PrefixesPermitted :: AsType (VerificationKey CommitteeHotKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey CommitteeHotKey)
_ = [Text
"cc_hot_vk"]

instance SerialiseAsBech32 (SigningKey CommitteeHotKey) where
  bech32PrefixFor :: SigningKey CommitteeHotKey -> Text
bech32PrefixFor SigningKey CommitteeHotKey
_ = Text
"cc_hot_sk"
  bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey CommitteeHotKey)
_ = [Text
"cc_hot_sk"]

--
-- Constitutional Committee Cold Keys
--

data CommitteeColdKey

instance HasTypeProxy CommitteeColdKey where
  data AsType CommitteeColdKey = AsCommitteeColdKey
  proxyToAsType :: Proxy CommitteeColdKey -> AsType CommitteeColdKey
proxyToAsType Proxy CommitteeColdKey
_ = AsType CommitteeColdKey
AsCommitteeColdKey

instance Key CommitteeColdKey where
  newtype VerificationKey CommitteeColdKey
    = CommitteeColdVerificationKey (Shelley.VKey Shelley.ColdCommitteeRole)
    deriving stock VerificationKey CommitteeColdKey
-> VerificationKey CommitteeColdKey -> Bool
(VerificationKey CommitteeColdKey
 -> VerificationKey CommitteeColdKey -> Bool)
-> (VerificationKey CommitteeColdKey
    -> VerificationKey CommitteeColdKey -> Bool)
-> Eq (VerificationKey CommitteeColdKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey CommitteeColdKey
-> VerificationKey CommitteeColdKey -> Bool
== :: VerificationKey CommitteeColdKey
-> VerificationKey CommitteeColdKey -> Bool
$c/= :: VerificationKey CommitteeColdKey
-> VerificationKey CommitteeColdKey -> Bool
/= :: VerificationKey CommitteeColdKey
-> VerificationKey CommitteeColdKey -> Bool
Eq
    deriving (Int -> VerificationKey CommitteeColdKey -> ShowS
[VerificationKey CommitteeColdKey] -> ShowS
VerificationKey CommitteeColdKey -> String
(Int -> VerificationKey CommitteeColdKey -> ShowS)
-> (VerificationKey CommitteeColdKey -> String)
-> ([VerificationKey CommitteeColdKey] -> ShowS)
-> Show (VerificationKey CommitteeColdKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey CommitteeColdKey -> ShowS
showsPrec :: Int -> VerificationKey CommitteeColdKey -> ShowS
$cshow :: VerificationKey CommitteeColdKey -> String
show :: VerificationKey CommitteeColdKey -> String
$cshowList :: [VerificationKey CommitteeColdKey] -> ShowS
showList :: [VerificationKey CommitteeColdKey] -> ShowS
Show, String -> VerificationKey CommitteeColdKey
(String -> VerificationKey CommitteeColdKey)
-> IsString (VerificationKey CommitteeColdKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey CommitteeColdKey
fromString :: String -> VerificationKey CommitteeColdKey
IsString) via UsingRawBytesHex (VerificationKey CommitteeColdKey)
    deriving newtype (Typeable (VerificationKey CommitteeColdKey)
Typeable (VerificationKey CommitteeColdKey) =>
(VerificationKey CommitteeColdKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey CommitteeColdKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey CommitteeColdKey] -> Size)
-> ToCBOR (VerificationKey CommitteeColdKey)
VerificationKey CommitteeColdKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey CommitteeColdKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey CommitteeColdKey) -> 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
$ctoCBOR :: VerificationKey CommitteeColdKey -> Encoding
toCBOR :: VerificationKey CommitteeColdKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey CommitteeColdKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey CommitteeColdKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey CommitteeColdKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey CommitteeColdKey] -> Size
ToCBOR, Typeable (VerificationKey CommitteeColdKey)
Typeable (VerificationKey CommitteeColdKey) =>
(forall s. Decoder s (VerificationKey CommitteeColdKey))
-> (Proxy (VerificationKey CommitteeColdKey) -> Text)
-> FromCBOR (VerificationKey CommitteeColdKey)
Proxy (VerificationKey CommitteeColdKey) -> Text
forall s. Decoder s (VerificationKey CommitteeColdKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey CommitteeColdKey)
fromCBOR :: forall s. Decoder s (VerificationKey CommitteeColdKey)
$clabel :: Proxy (VerificationKey CommitteeColdKey) -> Text
label :: Proxy (VerificationKey CommitteeColdKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey CommitteeColdKey)
HasTypeProxy (VerificationKey CommitteeColdKey) =>
(VerificationKey CommitteeColdKey -> ByteString)
-> (AsType (VerificationKey CommitteeColdKey)
    -> ByteString
    -> Either DecoderError (VerificationKey CommitteeColdKey))
-> SerialiseAsCBOR (VerificationKey CommitteeColdKey)
AsType (VerificationKey CommitteeColdKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeColdKey)
VerificationKey CommitteeColdKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey CommitteeColdKey -> ByteString
serialiseToCBOR :: VerificationKey CommitteeColdKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey CommitteeColdKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeColdKey)
deserialiseFromCBOR :: AsType (VerificationKey CommitteeColdKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeColdKey)
SerialiseAsCBOR

  newtype SigningKey CommitteeColdKey
    = CommitteeColdSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey CommitteeColdKey -> ShowS
[SigningKey CommitteeColdKey] -> ShowS
SigningKey CommitteeColdKey -> String
(Int -> SigningKey CommitteeColdKey -> ShowS)
-> (SigningKey CommitteeColdKey -> String)
-> ([SigningKey CommitteeColdKey] -> ShowS)
-> Show (SigningKey CommitteeColdKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey CommitteeColdKey -> ShowS
showsPrec :: Int -> SigningKey CommitteeColdKey -> ShowS
$cshow :: SigningKey CommitteeColdKey -> String
show :: SigningKey CommitteeColdKey -> String
$cshowList :: [SigningKey CommitteeColdKey] -> ShowS
showList :: [SigningKey CommitteeColdKey] -> ShowS
Show, String -> SigningKey CommitteeColdKey
(String -> SigningKey CommitteeColdKey)
-> IsString (SigningKey CommitteeColdKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey CommitteeColdKey
fromString :: String -> SigningKey CommitteeColdKey
IsString) via UsingRawBytesHex (SigningKey CommitteeColdKey)
    deriving newtype (Typeable (SigningKey CommitteeColdKey)
Typeable (SigningKey CommitteeColdKey) =>
(SigningKey CommitteeColdKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey CommitteeColdKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey CommitteeColdKey] -> Size)
-> ToCBOR (SigningKey CommitteeColdKey)
SigningKey CommitteeColdKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey CommitteeColdKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey CommitteeColdKey) -> 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
$ctoCBOR :: SigningKey CommitteeColdKey -> Encoding
toCBOR :: SigningKey CommitteeColdKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey CommitteeColdKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey CommitteeColdKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey CommitteeColdKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey CommitteeColdKey] -> Size
ToCBOR, Typeable (SigningKey CommitteeColdKey)
Typeable (SigningKey CommitteeColdKey) =>
(forall s. Decoder s (SigningKey CommitteeColdKey))
-> (Proxy (SigningKey CommitteeColdKey) -> Text)
-> FromCBOR (SigningKey CommitteeColdKey)
Proxy (SigningKey CommitteeColdKey) -> Text
forall s. Decoder s (SigningKey CommitteeColdKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey CommitteeColdKey)
fromCBOR :: forall s. Decoder s (SigningKey CommitteeColdKey)
$clabel :: Proxy (SigningKey CommitteeColdKey) -> Text
label :: Proxy (SigningKey CommitteeColdKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey CommitteeColdKey)
HasTypeProxy (SigningKey CommitteeColdKey) =>
(SigningKey CommitteeColdKey -> ByteString)
-> (AsType (SigningKey CommitteeColdKey)
    -> ByteString -> Either DecoderError (SigningKey CommitteeColdKey))
-> SerialiseAsCBOR (SigningKey CommitteeColdKey)
AsType (SigningKey CommitteeColdKey)
-> ByteString -> Either DecoderError (SigningKey CommitteeColdKey)
SigningKey CommitteeColdKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey CommitteeColdKey -> ByteString
serialiseToCBOR :: SigningKey CommitteeColdKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey CommitteeColdKey)
-> ByteString -> Either DecoderError (SigningKey CommitteeColdKey)
deserialiseFromCBOR :: AsType (SigningKey CommitteeColdKey)
-> ByteString -> Either DecoderError (SigningKey CommitteeColdKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType CommitteeColdKey -> Crypto.Seed -> SigningKey CommitteeColdKey
  deterministicSigningKey :: AsType CommitteeColdKey -> Seed -> SigningKey CommitteeColdKey
deterministicSigningKey AsType CommitteeColdKey
R:AsTypeCommitteeColdKey
AsCommitteeColdKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey CommitteeColdKey
CommitteeColdSigningKey (Seed -> SignKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)

  deterministicSigningKeySeedSize :: AsType CommitteeColdKey -> Word
  deterministicSigningKeySeedSize :: AsType CommitteeColdKey -> Word
deterministicSigningKeySeedSize AsType CommitteeColdKey
R:AsTypeCommitteeColdKey
AsCommitteeColdKey =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey CommitteeColdKey -> VerificationKey CommitteeColdKey
  getVerificationKey :: SigningKey CommitteeColdKey -> VerificationKey CommitteeColdKey
getVerificationKey (CommitteeColdSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'ColdCommitteeRole -> VerificationKey CommitteeColdKey
CommitteeColdVerificationKey (VerKeyDSIGN DSIGN -> VKey 'ColdCommitteeRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey CommitteeColdKey -> Hash CommitteeColdKey
  verificationKeyHash :: VerificationKey CommitteeColdKey -> Hash CommitteeColdKey
verificationKeyHash (CommitteeColdVerificationKey VKey 'ColdCommitteeRole
vkey) =
    KeyHash 'ColdCommitteeRole -> Hash CommitteeColdKey
CommitteeColdKeyHash (VKey 'ColdCommitteeRole -> KeyHash 'ColdCommitteeRole
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'ColdCommitteeRole
vkey)

instance SerialiseAsRawBytes (VerificationKey CommitteeColdKey) where
  serialiseToRawBytes :: VerificationKey CommitteeColdKey -> ByteString
serialiseToRawBytes (CommitteeColdVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey CommitteeColdKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeColdKey)
deserialiseFromRawBytes (AsVerificationKey AsType CommitteeColdKey
R:AsTypeCommitteeColdKey
AsCommitteeColdKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey CommitteeColdKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeColdKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey Constitutional Committee Cold Key")
      (Maybe (VerificationKey CommitteeColdKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey CommitteeColdKey))
-> Maybe (VerificationKey CommitteeColdKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeColdKey)
forall a b. (a -> b) -> a -> b
$ VKey 'ColdCommitteeRole -> VerificationKey CommitteeColdKey
CommitteeColdVerificationKey (VKey 'ColdCommitteeRole -> VerificationKey CommitteeColdKey)
-> (VerKeyDSIGN DSIGN -> VKey 'ColdCommitteeRole)
-> VerKeyDSIGN DSIGN
-> VerificationKey CommitteeColdKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'ColdCommitteeRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey CommitteeColdKey)
-> Maybe (VerKeyDSIGN DSIGN)
-> Maybe (VerificationKey CommitteeColdKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey CommitteeColdKey) where
  serialiseToRawBytes :: SigningKey CommitteeColdKey -> ByteString
serialiseToRawBytes (CommitteeColdSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey CommitteeColdKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey CommitteeColdKey)
deserialiseFromRawBytes (AsSigningKey AsType CommitteeColdKey
R:AsTypeCommitteeColdKey
AsCommitteeColdKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (SigningKey CommitteeColdKey)
-> Either SerialiseAsRawBytesError (SigningKey CommitteeColdKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey Constitutional Committee Cold Key")
      (Maybe (SigningKey CommitteeColdKey)
 -> Either SerialiseAsRawBytesError (SigningKey CommitteeColdKey))
-> Maybe (SigningKey CommitteeColdKey)
-> Either SerialiseAsRawBytesError (SigningKey CommitteeColdKey)
forall a b. (a -> b) -> a -> b
$ SignKeyDSIGN DSIGN -> SigningKey CommitteeColdKey
CommitteeColdSigningKey (SignKeyDSIGN DSIGN -> SigningKey CommitteeColdKey)
-> Maybe (SignKeyDSIGN DSIGN)
-> Maybe (SigningKey CommitteeColdKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs

newtype instance Hash CommitteeColdKey
  = CommitteeColdKeyHash
  {Hash CommitteeColdKey -> KeyHash 'ColdCommitteeRole
unCommitteeColdKeyHash :: Shelley.KeyHash Shelley.ColdCommitteeRole}
  deriving stock (Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
(Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool)
-> (Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool)
-> Eq (Hash CommitteeColdKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
== :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
$c/= :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
/= :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
Eq, Eq (Hash CommitteeColdKey)
Eq (Hash CommitteeColdKey) =>
(Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering)
-> (Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool)
-> (Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool)
-> (Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool)
-> (Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool)
-> (Hash CommitteeColdKey
    -> Hash CommitteeColdKey -> Hash CommitteeColdKey)
-> (Hash CommitteeColdKey
    -> Hash CommitteeColdKey -> Hash CommitteeColdKey)
-> Ord (Hash CommitteeColdKey)
Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering
Hash CommitteeColdKey
-> Hash CommitteeColdKey -> Hash CommitteeColdKey
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
$ccompare :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering
compare :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering
$c< :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
< :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
$c<= :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
<= :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
$c> :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
> :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
$c>= :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
>= :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool
$cmax :: Hash CommitteeColdKey
-> Hash CommitteeColdKey -> Hash CommitteeColdKey
max :: Hash CommitteeColdKey
-> Hash CommitteeColdKey -> Hash CommitteeColdKey
$cmin :: Hash CommitteeColdKey
-> Hash CommitteeColdKey -> Hash CommitteeColdKey
min :: Hash CommitteeColdKey
-> Hash CommitteeColdKey -> Hash CommitteeColdKey
Ord)
  deriving (Int -> Hash CommitteeColdKey -> ShowS
[Hash CommitteeColdKey] -> ShowS
Hash CommitteeColdKey -> String
(Int -> Hash CommitteeColdKey -> ShowS)
-> (Hash CommitteeColdKey -> String)
-> ([Hash CommitteeColdKey] -> ShowS)
-> Show (Hash CommitteeColdKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash CommitteeColdKey -> ShowS
showsPrec :: Int -> Hash CommitteeColdKey -> ShowS
$cshow :: Hash CommitteeColdKey -> String
show :: Hash CommitteeColdKey -> String
$cshowList :: [Hash CommitteeColdKey] -> ShowS
showList :: [Hash CommitteeColdKey] -> ShowS
Show, String -> Hash CommitteeColdKey
(String -> Hash CommitteeColdKey)
-> IsString (Hash CommitteeColdKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash CommitteeColdKey
fromString :: String -> Hash CommitteeColdKey
IsString) via UsingRawBytesHex (Hash CommitteeColdKey)
  deriving (Typeable (Hash CommitteeColdKey)
Typeable (Hash CommitteeColdKey) =>
(Hash CommitteeColdKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash CommitteeColdKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash CommitteeColdKey] -> Size)
-> ToCBOR (Hash CommitteeColdKey)
Hash CommitteeColdKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeColdKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeColdKey) -> 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
$ctoCBOR :: Hash CommitteeColdKey -> Encoding
toCBOR :: Hash CommitteeColdKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeColdKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeColdKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeColdKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeColdKey] -> Size
ToCBOR, Typeable (Hash CommitteeColdKey)
Typeable (Hash CommitteeColdKey) =>
(forall s. Decoder s (Hash CommitteeColdKey))
-> (Proxy (Hash CommitteeColdKey) -> Text)
-> FromCBOR (Hash CommitteeColdKey)
Proxy (Hash CommitteeColdKey) -> Text
forall s. Decoder s (Hash CommitteeColdKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash CommitteeColdKey)
fromCBOR :: forall s. Decoder s (Hash CommitteeColdKey)
$clabel :: Proxy (Hash CommitteeColdKey) -> Text
label :: Proxy (Hash CommitteeColdKey) -> Text
FromCBOR) via UsingRawBytes (Hash CommitteeColdKey)
  deriving anyclass HasTypeProxy (Hash CommitteeColdKey)
HasTypeProxy (Hash CommitteeColdKey) =>
(Hash CommitteeColdKey -> ByteString)
-> (AsType (Hash CommitteeColdKey)
    -> ByteString -> Either DecoderError (Hash CommitteeColdKey))
-> SerialiseAsCBOR (Hash CommitteeColdKey)
AsType (Hash CommitteeColdKey)
-> ByteString -> Either DecoderError (Hash CommitteeColdKey)
Hash CommitteeColdKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash CommitteeColdKey -> ByteString
serialiseToCBOR :: Hash CommitteeColdKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash CommitteeColdKey)
-> ByteString -> Either DecoderError (Hash CommitteeColdKey)
deserialiseFromCBOR :: AsType (Hash CommitteeColdKey)
-> ByteString -> Either DecoderError (Hash CommitteeColdKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash CommitteeColdKey) where
  serialiseToRawBytes :: Hash CommitteeColdKey -> ByteString
serialiseToRawBytes (CommitteeColdKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash CommitteeColdKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash CommitteeColdKey)
deserialiseFromRawBytes (AsHash AsType CommitteeColdKey
R:AsTypeCommitteeColdKey
AsCommitteeColdKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash CommitteeColdKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeColdKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash Constitutional Committee Cold Key")
      (Maybe (Hash CommitteeColdKey)
 -> Either SerialiseAsRawBytesError (Hash CommitteeColdKey))
-> Maybe (Hash CommitteeColdKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeColdKey)
forall a b. (a -> b) -> a -> b
$ KeyHash 'ColdCommitteeRole -> Hash CommitteeColdKey
CommitteeColdKeyHash (KeyHash 'ColdCommitteeRole -> Hash CommitteeColdKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN)
    -> KeyHash 'ColdCommitteeRole)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash CommitteeColdKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'ColdCommitteeRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash CommitteeColdKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash CommitteeColdKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey CommitteeColdKey) where
  textEnvelopeType :: AsType (VerificationKey CommitteeColdKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey CommitteeColdKey)
_ =
    TextEnvelopeType
"ConstitutionalCommitteeColdVerificationKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey CommitteeColdKey) where
  textEnvelopeType :: AsType (SigningKey CommitteeColdKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey CommitteeColdKey)
_ =
    TextEnvelopeType
"ConstitutionalCommitteeColdSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance CastVerificationKeyRole CommitteeColdKey PaymentKey where
  castVerificationKey :: VerificationKey CommitteeColdKey -> VerificationKey PaymentKey
castVerificationKey (CommitteeColdVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VKey 'Payment -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey VerKeyDSIGN DSIGN
vk)

instance SerialiseAsBech32 (Hash CommitteeColdKey) where
  bech32PrefixFor :: Hash CommitteeColdKey -> Text
bech32PrefixFor Hash CommitteeColdKey
_ = Text
"cc_cold"
  bech32PrefixesPermitted :: AsType (Hash CommitteeColdKey) -> [Text]
bech32PrefixesPermitted AsType (Hash CommitteeColdKey)
_ = [Text
"cc_cold"]

instance SerialiseAsBech32 (VerificationKey CommitteeColdKey) where
  bech32PrefixFor :: VerificationKey CommitteeColdKey -> Text
bech32PrefixFor VerificationKey CommitteeColdKey
_ = Text
"cc_cold_vk"
  bech32PrefixesPermitted :: AsType (VerificationKey CommitteeColdKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey CommitteeColdKey)
_ = [Text
"cc_cold_vk"]

instance SerialiseAsBech32 (SigningKey CommitteeColdKey) where
  bech32PrefixFor :: SigningKey CommitteeColdKey -> Text
bech32PrefixFor SigningKey CommitteeColdKey
_ = Text
"cc_cold_sk"
  bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey CommitteeColdKey)
_ = [Text
"cc_cold_sk"]

---
--- Committee cold extended keys
---
data CommitteeColdExtendedKey

instance HasTypeProxy CommitteeColdExtendedKey where
  data AsType CommitteeColdExtendedKey = AsCommitteeColdExtendedKey
  proxyToAsType :: Proxy CommitteeColdExtendedKey -> AsType CommitteeColdExtendedKey
proxyToAsType Proxy CommitteeColdExtendedKey
_ = AsType CommitteeColdExtendedKey
AsCommitteeColdExtendedKey

instance Key CommitteeColdExtendedKey where
  newtype VerificationKey CommitteeColdExtendedKey
    = CommitteeColdExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdExtendedKey -> Bool
(VerificationKey CommitteeColdExtendedKey
 -> VerificationKey CommitteeColdExtendedKey -> Bool)
-> (VerificationKey CommitteeColdExtendedKey
    -> VerificationKey CommitteeColdExtendedKey -> Bool)
-> Eq (VerificationKey CommitteeColdExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdExtendedKey -> Bool
== :: VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdExtendedKey -> Bool
$c/= :: VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdExtendedKey -> Bool
/= :: VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey CommitteeColdExtendedKey)
HasTypeProxy (VerificationKey CommitteeColdExtendedKey) =>
(VerificationKey CommitteeColdExtendedKey -> ByteString)
-> (AsType (VerificationKey CommitteeColdExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey CommitteeColdExtendedKey))
-> SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey)
AsType (VerificationKey CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeColdExtendedKey)
VerificationKey CommitteeColdExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey CommitteeColdExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey CommitteeColdExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeColdExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeColdExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey CommitteeColdExtendedKey -> ShowS
[VerificationKey CommitteeColdExtendedKey] -> ShowS
VerificationKey CommitteeColdExtendedKey -> String
(Int -> VerificationKey CommitteeColdExtendedKey -> ShowS)
-> (VerificationKey CommitteeColdExtendedKey -> String)
-> ([VerificationKey CommitteeColdExtendedKey] -> ShowS)
-> Show (VerificationKey CommitteeColdExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey CommitteeColdExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey CommitteeColdExtendedKey -> ShowS
$cshow :: VerificationKey CommitteeColdExtendedKey -> String
show :: VerificationKey CommitteeColdExtendedKey -> String
$cshowList :: [VerificationKey CommitteeColdExtendedKey] -> ShowS
showList :: [VerificationKey CommitteeColdExtendedKey] -> ShowS
Show, String -> VerificationKey CommitteeColdExtendedKey
(String -> VerificationKey CommitteeColdExtendedKey)
-> IsString (VerificationKey CommitteeColdExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey CommitteeColdExtendedKey
fromString :: String -> VerificationKey CommitteeColdExtendedKey
IsString) via UsingRawBytesHex (VerificationKey PaymentExtendedKey)

  newtype SigningKey CommitteeColdExtendedKey
    = CommitteeColdExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey CommitteeColdExtendedKey)
HasTypeProxy (SigningKey CommitteeColdExtendedKey) =>
(SigningKey CommitteeColdExtendedKey -> ByteString)
-> (AsType (SigningKey CommitteeColdExtendedKey)
    -> ByteString
    -> Either DecoderError (SigningKey CommitteeColdExtendedKey))
-> SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey)
AsType (SigningKey CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey CommitteeColdExtendedKey)
SigningKey CommitteeColdExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey CommitteeColdExtendedKey -> ByteString
serialiseToCBOR :: SigningKey CommitteeColdExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey CommitteeColdExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey CommitteeColdExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey CommitteeColdExtendedKey -> ShowS
[SigningKey CommitteeColdExtendedKey] -> ShowS
SigningKey CommitteeColdExtendedKey -> String
(Int -> SigningKey CommitteeColdExtendedKey -> ShowS)
-> (SigningKey CommitteeColdExtendedKey -> String)
-> ([SigningKey CommitteeColdExtendedKey] -> ShowS)
-> Show (SigningKey CommitteeColdExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey CommitteeColdExtendedKey -> ShowS
showsPrec :: Int -> SigningKey CommitteeColdExtendedKey -> ShowS
$cshow :: SigningKey CommitteeColdExtendedKey -> String
show :: SigningKey CommitteeColdExtendedKey -> String
$cshowList :: [SigningKey CommitteeColdExtendedKey] -> ShowS
showList :: [SigningKey CommitteeColdExtendedKey] -> ShowS
Show, String -> SigningKey CommitteeColdExtendedKey
(String -> SigningKey CommitteeColdExtendedKey)
-> IsString (SigningKey CommitteeColdExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey CommitteeColdExtendedKey
fromString :: String -> SigningKey CommitteeColdExtendedKey
IsString) via UsingRawBytesHex (SigningKey PaymentExtendedKey)

  deterministicSigningKey
    :: AsType CommitteeColdExtendedKey
    -> Crypto.Seed
    -> SigningKey CommitteeColdExtendedKey
  deterministicSigningKey :: AsType CommitteeColdExtendedKey
-> Seed -> SigningKey CommitteeColdExtendedKey
deterministicSigningKey AsType CommitteeColdExtendedKey
R:AsTypeCommitteeColdExtendedKey
AsCommitteeColdExtendedKey Seed
seed =
    XPrv -> SigningKey CommitteeColdExtendedKey
CommitteeColdExtendedSigningKey
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType CommitteeColdExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType CommitteeColdExtendedKey -> Word
deterministicSigningKeySeedSize AsType CommitteeColdExtendedKey
R:AsTypeCommitteeColdExtendedKey
AsCommitteeColdExtendedKey = Word
32

  getVerificationKey
    :: SigningKey CommitteeColdExtendedKey
    -> VerificationKey CommitteeColdExtendedKey
  getVerificationKey :: SigningKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdExtendedKey
getVerificationKey (CommitteeColdExtendedSigningKey XPrv
sk) =
    XPub -> VerificationKey CommitteeColdExtendedKey
CommitteeColdExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey
  verificationKeyHash :: VerificationKey CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey
verificationKeyHash (CommitteeColdExtendedVerificationKey XPub
vk) =
    KeyHash 'ColdCommitteeRole -> Hash CommitteeColdExtendedKey
CommitteeColdExtendedKeyHash
      (KeyHash 'ColdCommitteeRole -> Hash CommitteeColdExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'ColdCommitteeRole)
-> Hash ADDRHASH XPub
-> Hash CommitteeColdExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'ColdCommitteeRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'ColdCommitteeRole)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'ColdCommitteeRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash CommitteeColdExtendedKey)
-> Hash ADDRHASH XPub -> Hash CommitteeColdExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

newtype instance Hash CommitteeColdExtendedKey
  = CommitteeColdExtendedKeyHash
  {Hash CommitteeColdExtendedKey -> KeyHash 'ColdCommitteeRole
unCommitteeColdExtendedKeyHash :: Shelley.KeyHash Shelley.ColdCommitteeRole}
  deriving stock (Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
(Hash CommitteeColdExtendedKey
 -> Hash CommitteeColdExtendedKey -> Bool)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Bool)
-> Eq (Hash CommitteeColdExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
== :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
$c/= :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
/= :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
Eq, Eq (Hash CommitteeColdExtendedKey)
Eq (Hash CommitteeColdExtendedKey) =>
(Hash CommitteeColdExtendedKey
 -> Hash CommitteeColdExtendedKey -> Ordering)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Bool)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Bool)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Bool)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Bool)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey)
-> (Hash CommitteeColdExtendedKey
    -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey)
-> Ord (Hash CommitteeColdExtendedKey)
Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Ordering
Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey
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
$ccompare :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Ordering
compare :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Ordering
$c< :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
< :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
$c<= :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
<= :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
$c> :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
> :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
$c>= :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
>= :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Bool
$cmax :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey
max :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey
$cmin :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey
min :: Hash CommitteeColdExtendedKey
-> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey
Ord)
  deriving (Int -> Hash CommitteeColdExtendedKey -> ShowS
[Hash CommitteeColdExtendedKey] -> ShowS
Hash CommitteeColdExtendedKey -> String
(Int -> Hash CommitteeColdExtendedKey -> ShowS)
-> (Hash CommitteeColdExtendedKey -> String)
-> ([Hash CommitteeColdExtendedKey] -> ShowS)
-> Show (Hash CommitteeColdExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash CommitteeColdExtendedKey -> ShowS
showsPrec :: Int -> Hash CommitteeColdExtendedKey -> ShowS
$cshow :: Hash CommitteeColdExtendedKey -> String
show :: Hash CommitteeColdExtendedKey -> String
$cshowList :: [Hash CommitteeColdExtendedKey] -> ShowS
showList :: [Hash CommitteeColdExtendedKey] -> ShowS
Show, String -> Hash CommitteeColdExtendedKey
(String -> Hash CommitteeColdExtendedKey)
-> IsString (Hash CommitteeColdExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash CommitteeColdExtendedKey
fromString :: String -> Hash CommitteeColdExtendedKey
IsString) via UsingRawBytesHex (Hash CommitteeColdKey)
  deriving (Typeable (Hash CommitteeColdExtendedKey)
Typeable (Hash CommitteeColdExtendedKey) =>
(Hash CommitteeColdExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash CommitteeColdExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash CommitteeColdExtendedKey] -> Size)
-> ToCBOR (Hash CommitteeColdExtendedKey)
Hash CommitteeColdExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeColdExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeColdExtendedKey) -> 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
$ctoCBOR :: Hash CommitteeColdExtendedKey -> Encoding
toCBOR :: Hash CommitteeColdExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeColdExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeColdExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeColdExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeColdExtendedKey] -> Size
ToCBOR, Typeable (Hash CommitteeColdExtendedKey)
Typeable (Hash CommitteeColdExtendedKey) =>
(forall s. Decoder s (Hash CommitteeColdExtendedKey))
-> (Proxy (Hash CommitteeColdExtendedKey) -> Text)
-> FromCBOR (Hash CommitteeColdExtendedKey)
Proxy (Hash CommitteeColdExtendedKey) -> Text
forall s. Decoder s (Hash CommitteeColdExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash CommitteeColdExtendedKey)
fromCBOR :: forall s. Decoder s (Hash CommitteeColdExtendedKey)
$clabel :: Proxy (Hash CommitteeColdExtendedKey) -> Text
label :: Proxy (Hash CommitteeColdExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash CommitteeColdKey)
  deriving anyclass HasTypeProxy (Hash CommitteeColdExtendedKey)
HasTypeProxy (Hash CommitteeColdExtendedKey) =>
(Hash CommitteeColdExtendedKey -> ByteString)
-> (AsType (Hash CommitteeColdExtendedKey)
    -> ByteString
    -> Either DecoderError (Hash CommitteeColdExtendedKey))
-> SerialiseAsCBOR (Hash CommitteeColdExtendedKey)
AsType (Hash CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (Hash CommitteeColdExtendedKey)
Hash CommitteeColdExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash CommitteeColdExtendedKey -> ByteString
serialiseToCBOR :: Hash CommitteeColdExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (Hash CommitteeColdExtendedKey)
deserialiseFromCBOR :: AsType (Hash CommitteeColdExtendedKey)
-> ByteString
-> Either DecoderError (Hash CommitteeColdExtendedKey)
SerialiseAsCBOR

instance ToCBOR (VerificationKey CommitteeColdExtendedKey) where
  toCBOR :: VerificationKey CommitteeColdExtendedKey -> Encoding
toCBOR (CommitteeColdExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)

instance FromCBOR (VerificationKey CommitteeColdExtendedKey) where
  fromCBOR :: forall s. Decoder s (VerificationKey CommitteeColdExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey CommitteeColdExtendedKey))
-> (XPub -> Decoder s (VerificationKey CommitteeColdExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey CommitteeColdExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey CommitteeColdExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey CommitteeColdExtendedKey
-> Decoder s (VerificationKey CommitteeColdExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey CommitteeColdExtendedKey
 -> Decoder s (VerificationKey CommitteeColdExtendedKey))
-> (XPub -> VerificationKey CommitteeColdExtendedKey)
-> XPub
-> Decoder s (VerificationKey CommitteeColdExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey CommitteeColdExtendedKey
CommitteeColdExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey CommitteeColdExtendedKey) where
  toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding
toCBOR (CommitteeColdExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)

instance FromCBOR (SigningKey CommitteeColdExtendedKey) where
  fromCBOR :: forall s. Decoder s (SigningKey CommitteeColdExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey CommitteeColdExtendedKey))
-> (XPrv -> Decoder s (SigningKey CommitteeColdExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey CommitteeColdExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey CommitteeColdExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey CommitteeColdExtendedKey
-> Decoder s (SigningKey CommitteeColdExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey CommitteeColdExtendedKey
 -> Decoder s (SigningKey CommitteeColdExtendedKey))
-> (XPrv -> SigningKey CommitteeColdExtendedKey)
-> XPrv
-> Decoder s (SigningKey CommitteeColdExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey CommitteeColdExtendedKey
CommitteeColdExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) where
  serialiseToRawBytes :: VerificationKey CommitteeColdExtendedKey -> ByteString
serialiseToRawBytes (CommitteeColdExtendedVerificationKey XPub
xpub) =
    XPub -> ByteString
Crypto.HD.unXPub XPub
xpub

  deserialiseFromRawBytes :: AsType (VerificationKey CommitteeColdExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeColdExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType CommitteeColdExtendedKey
R:AsTypeCommitteeColdExtendedKey
AsCommitteeColdExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey CommitteeColdExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeColdExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey CommitteeColdExtendedKey"))
      (XPub -> VerificationKey CommitteeColdExtendedKey
CommitteeColdExtendedVerificationKey (XPub -> VerificationKey CommitteeColdExtendedKey)
-> Either String XPub
-> Either String (VerificationKey CommitteeColdExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)

instance SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) where
  serialiseToRawBytes :: SigningKey CommitteeColdExtendedKey -> ByteString
serialiseToRawBytes (CommitteeColdExtendedSigningKey XPrv
xprv) =
    XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv

  deserialiseFromRawBytes :: AsType (SigningKey CommitteeColdExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (SigningKey CommitteeColdExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType CommitteeColdExtendedKey
R:AsTypeCommitteeColdExtendedKey
AsCommitteeColdExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey CommitteeColdExtendedKey)
-> Either
     SerialiseAsRawBytesError (SigningKey CommitteeColdExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey CommitteeColdExtendedKey"))
      (XPrv -> SigningKey CommitteeColdExtendedKey
CommitteeColdExtendedSigningKey (XPrv -> SigningKey CommitteeColdExtendedKey)
-> Either String XPrv
-> Either String (SigningKey CommitteeColdExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)

instance SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) where
  serialiseToRawBytes :: Hash CommitteeColdExtendedKey -> ByteString
serialiseToRawBytes (CommitteeColdExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash CommitteeColdExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash CommitteeColdExtendedKey)
deserialiseFromRawBytes (AsHash AsType CommitteeColdExtendedKey
R:AsTypeCommitteeColdExtendedKey
AsCommitteeColdExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash CommitteeColdExtendedKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeColdExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash CommitteeColdExtendedKey") (Maybe (Hash CommitteeColdExtendedKey)
 -> Either SerialiseAsRawBytesError (Hash CommitteeColdExtendedKey))
-> Maybe (Hash CommitteeColdExtendedKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeColdExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'ColdCommitteeRole -> Hash CommitteeColdExtendedKey
CommitteeColdExtendedKeyHash (KeyHash 'ColdCommitteeRole -> Hash CommitteeColdExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN)
    -> KeyHash 'ColdCommitteeRole)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash CommitteeColdExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'ColdCommitteeRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN)
 -> Hash CommitteeColdExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash CommitteeColdExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) where
  textEnvelopeType :: AsType (VerificationKey CommitteeColdExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey CommitteeColdExtendedKey)
_ = TextEnvelopeType
"ConstitutionalCommitteeColdExtendedVerificationKey_ed25519_bip32"

instance HasTextEnvelope (SigningKey CommitteeColdExtendedKey) where
  textEnvelopeType :: AsType (SigningKey CommitteeColdExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey CommitteeColdExtendedKey)
_ = TextEnvelopeType
"ConstitutionalCommitteeColdExtendedSigningKey_ed25519_bip32"

instance SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) where
  bech32PrefixFor :: VerificationKey CommitteeColdExtendedKey -> Text
bech32PrefixFor VerificationKey CommitteeColdExtendedKey
_ = Text
"cc_cold_xvk"
  bech32PrefixesPermitted :: AsType (VerificationKey CommitteeColdExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey CommitteeColdExtendedKey)
_ = [Text
"cc_cold_xvk"]

instance SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) where
  bech32PrefixFor :: SigningKey CommitteeColdExtendedKey -> Text
bech32PrefixFor SigningKey CommitteeColdExtendedKey
_ = Text
"cc_cold_xsk"
  bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey CommitteeColdExtendedKey)
_ = [Text
"cc_cold_xsk"]

instance CastVerificationKeyRole CommitteeColdExtendedKey CommitteeColdKey where
  castVerificationKey :: VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdKey
castVerificationKey (CommitteeColdExtendedVerificationKey XPub
vk) =
    VKey 'ColdCommitteeRole -> VerificationKey CommitteeColdKey
CommitteeColdVerificationKey
      (VKey 'ColdCommitteeRole -> VerificationKey CommitteeColdKey)
-> (XPub -> VKey 'ColdCommitteeRole)
-> XPub
-> VerificationKey CommitteeColdKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'ColdCommitteeRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'ColdCommitteeRole)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'ColdCommitteeRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey CommitteeColdKey)
-> XPub -> VerificationKey CommitteeColdKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey (CommitteeCold): byron and shelley key sizes do not match!"

---
--- Committee hot extended keys
---
data CommitteeHotExtendedKey

instance HasTypeProxy CommitteeHotExtendedKey where
  data AsType CommitteeHotExtendedKey = AsCommitteeHotExtendedKey
  proxyToAsType :: Proxy CommitteeHotExtendedKey -> AsType CommitteeHotExtendedKey
proxyToAsType Proxy CommitteeHotExtendedKey
_ = AsType CommitteeHotExtendedKey
AsCommitteeHotExtendedKey

instance Key CommitteeHotExtendedKey where
  newtype VerificationKey CommitteeHotExtendedKey
    = CommitteeHotExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotExtendedKey -> Bool
(VerificationKey CommitteeHotExtendedKey
 -> VerificationKey CommitteeHotExtendedKey -> Bool)
-> (VerificationKey CommitteeHotExtendedKey
    -> VerificationKey CommitteeHotExtendedKey -> Bool)
-> Eq (VerificationKey CommitteeHotExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotExtendedKey -> Bool
== :: VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotExtendedKey -> Bool
$c/= :: VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotExtendedKey -> Bool
/= :: VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey CommitteeHotExtendedKey)
HasTypeProxy (VerificationKey CommitteeHotExtendedKey) =>
(VerificationKey CommitteeHotExtendedKey -> ByteString)
-> (AsType (VerificationKey CommitteeHotExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey CommitteeHotExtendedKey))
-> SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey)
AsType (VerificationKey CommitteeHotExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeHotExtendedKey)
VerificationKey CommitteeHotExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey CommitteeHotExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey CommitteeHotExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey CommitteeHotExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeHotExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey CommitteeHotExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey CommitteeHotExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey CommitteeHotExtendedKey -> ShowS
[VerificationKey CommitteeHotExtendedKey] -> ShowS
VerificationKey CommitteeHotExtendedKey -> String
(Int -> VerificationKey CommitteeHotExtendedKey -> ShowS)
-> (VerificationKey CommitteeHotExtendedKey -> String)
-> ([VerificationKey CommitteeHotExtendedKey] -> ShowS)
-> Show (VerificationKey CommitteeHotExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey CommitteeHotExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey CommitteeHotExtendedKey -> ShowS
$cshow :: VerificationKey CommitteeHotExtendedKey -> String
show :: VerificationKey CommitteeHotExtendedKey -> String
$cshowList :: [VerificationKey CommitteeHotExtendedKey] -> ShowS
showList :: [VerificationKey CommitteeHotExtendedKey] -> ShowS
Show, String -> VerificationKey CommitteeHotExtendedKey
(String -> VerificationKey CommitteeHotExtendedKey)
-> IsString (VerificationKey CommitteeHotExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey CommitteeHotExtendedKey
fromString :: String -> VerificationKey CommitteeHotExtendedKey
IsString) via UsingRawBytesHex (VerificationKey PaymentExtendedKey)

  newtype SigningKey CommitteeHotExtendedKey
    = CommitteeHotExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey CommitteeHotExtendedKey)
HasTypeProxy (SigningKey CommitteeHotExtendedKey) =>
(SigningKey CommitteeHotExtendedKey -> ByteString)
-> (AsType (SigningKey CommitteeHotExtendedKey)
    -> ByteString
    -> Either DecoderError (SigningKey CommitteeHotExtendedKey))
-> SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey)
AsType (SigningKey CommitteeHotExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey CommitteeHotExtendedKey)
SigningKey CommitteeHotExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey CommitteeHotExtendedKey -> ByteString
serialiseToCBOR :: SigningKey CommitteeHotExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey CommitteeHotExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey CommitteeHotExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey CommitteeHotExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey CommitteeHotExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey CommitteeHotExtendedKey -> ShowS
[SigningKey CommitteeHotExtendedKey] -> ShowS
SigningKey CommitteeHotExtendedKey -> String
(Int -> SigningKey CommitteeHotExtendedKey -> ShowS)
-> (SigningKey CommitteeHotExtendedKey -> String)
-> ([SigningKey CommitteeHotExtendedKey] -> ShowS)
-> Show (SigningKey CommitteeHotExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey CommitteeHotExtendedKey -> ShowS
showsPrec :: Int -> SigningKey CommitteeHotExtendedKey -> ShowS
$cshow :: SigningKey CommitteeHotExtendedKey -> String
show :: SigningKey CommitteeHotExtendedKey -> String
$cshowList :: [SigningKey CommitteeHotExtendedKey] -> ShowS
showList :: [SigningKey CommitteeHotExtendedKey] -> ShowS
Show, String -> SigningKey CommitteeHotExtendedKey
(String -> SigningKey CommitteeHotExtendedKey)
-> IsString (SigningKey CommitteeHotExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey CommitteeHotExtendedKey
fromString :: String -> SigningKey CommitteeHotExtendedKey
IsString) via UsingRawBytesHex (SigningKey PaymentExtendedKey)

  deterministicSigningKey
    :: AsType CommitteeHotExtendedKey
    -> Crypto.Seed
    -> SigningKey CommitteeHotExtendedKey
  deterministicSigningKey :: AsType CommitteeHotExtendedKey
-> Seed -> SigningKey CommitteeHotExtendedKey
deterministicSigningKey AsType CommitteeHotExtendedKey
R:AsTypeCommitteeHotExtendedKey
AsCommitteeHotExtendedKey Seed
seed =
    XPrv -> SigningKey CommitteeHotExtendedKey
CommitteeHotExtendedSigningKey
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType CommitteeHotExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType CommitteeHotExtendedKey -> Word
deterministicSigningKeySeedSize AsType CommitteeHotExtendedKey
R:AsTypeCommitteeHotExtendedKey
AsCommitteeHotExtendedKey = Word
32

  getVerificationKey
    :: SigningKey CommitteeHotExtendedKey
    -> VerificationKey CommitteeHotExtendedKey
  getVerificationKey :: SigningKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotExtendedKey
getVerificationKey (CommitteeHotExtendedSigningKey XPrv
sk) =
    XPub -> VerificationKey CommitteeHotExtendedKey
CommitteeHotExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey
  verificationKeyHash :: VerificationKey CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey
verificationKeyHash (CommitteeHotExtendedVerificationKey XPub
vk) =
    KeyHash 'HotCommitteeRole -> Hash CommitteeHotExtendedKey
CommitteeHotExtendedKeyHash
      (KeyHash 'HotCommitteeRole -> Hash CommitteeHotExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'HotCommitteeRole)
-> Hash ADDRHASH XPub
-> Hash CommitteeHotExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'HotCommitteeRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'HotCommitteeRole)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'HotCommitteeRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash CommitteeHotExtendedKey)
-> Hash ADDRHASH XPub -> Hash CommitteeHotExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

newtype instance Hash CommitteeHotExtendedKey
  = CommitteeHotExtendedKeyHash
  {Hash CommitteeHotExtendedKey -> KeyHash 'HotCommitteeRole
unCommitteeHotExtendedKeyHash :: Shelley.KeyHash Shelley.HotCommitteeRole}
  deriving stock (Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
(Hash CommitteeHotExtendedKey
 -> Hash CommitteeHotExtendedKey -> Bool)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Bool)
-> Eq (Hash CommitteeHotExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
== :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
$c/= :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
/= :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
Eq, Eq (Hash CommitteeHotExtendedKey)
Eq (Hash CommitteeHotExtendedKey) =>
(Hash CommitteeHotExtendedKey
 -> Hash CommitteeHotExtendedKey -> Ordering)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Bool)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Bool)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Bool)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Bool)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey)
-> (Hash CommitteeHotExtendedKey
    -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey)
-> Ord (Hash CommitteeHotExtendedKey)
Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Ordering
Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey
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
$ccompare :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Ordering
compare :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Ordering
$c< :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
< :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
$c<= :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
<= :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
$c> :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
> :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
$c>= :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
>= :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Bool
$cmax :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey
max :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey
$cmin :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey
min :: Hash CommitteeHotExtendedKey
-> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey
Ord)
  deriving (Int -> Hash CommitteeHotExtendedKey -> ShowS
[Hash CommitteeHotExtendedKey] -> ShowS
Hash CommitteeHotExtendedKey -> String
(Int -> Hash CommitteeHotExtendedKey -> ShowS)
-> (Hash CommitteeHotExtendedKey -> String)
-> ([Hash CommitteeHotExtendedKey] -> ShowS)
-> Show (Hash CommitteeHotExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash CommitteeHotExtendedKey -> ShowS
showsPrec :: Int -> Hash CommitteeHotExtendedKey -> ShowS
$cshow :: Hash CommitteeHotExtendedKey -> String
show :: Hash CommitteeHotExtendedKey -> String
$cshowList :: [Hash CommitteeHotExtendedKey] -> ShowS
showList :: [Hash CommitteeHotExtendedKey] -> ShowS
Show, String -> Hash CommitteeHotExtendedKey
(String -> Hash CommitteeHotExtendedKey)
-> IsString (Hash CommitteeHotExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash CommitteeHotExtendedKey
fromString :: String -> Hash CommitteeHotExtendedKey
IsString) via UsingRawBytesHex (Hash CommitteeHotKey)
  deriving (Typeable (Hash CommitteeHotExtendedKey)
Typeable (Hash CommitteeHotExtendedKey) =>
(Hash CommitteeHotExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash CommitteeHotExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash CommitteeHotExtendedKey] -> Size)
-> ToCBOR (Hash CommitteeHotExtendedKey)
Hash CommitteeHotExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeHotExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeHotExtendedKey) -> 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
$ctoCBOR :: Hash CommitteeHotExtendedKey -> Encoding
toCBOR :: Hash CommitteeHotExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeHotExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash CommitteeHotExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeHotExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash CommitteeHotExtendedKey] -> Size
ToCBOR, Typeable (Hash CommitteeHotExtendedKey)
Typeable (Hash CommitteeHotExtendedKey) =>
(forall s. Decoder s (Hash CommitteeHotExtendedKey))
-> (Proxy (Hash CommitteeHotExtendedKey) -> Text)
-> FromCBOR (Hash CommitteeHotExtendedKey)
Proxy (Hash CommitteeHotExtendedKey) -> Text
forall s. Decoder s (Hash CommitteeHotExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash CommitteeHotExtendedKey)
fromCBOR :: forall s. Decoder s (Hash CommitteeHotExtendedKey)
$clabel :: Proxy (Hash CommitteeHotExtendedKey) -> Text
label :: Proxy (Hash CommitteeHotExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash CommitteeHotKey)
  deriving anyclass HasTypeProxy (Hash CommitteeHotExtendedKey)
HasTypeProxy (Hash CommitteeHotExtendedKey) =>
(Hash CommitteeHotExtendedKey -> ByteString)
-> (AsType (Hash CommitteeHotExtendedKey)
    -> ByteString
    -> Either DecoderError (Hash CommitteeHotExtendedKey))
-> SerialiseAsCBOR (Hash CommitteeHotExtendedKey)
AsType (Hash CommitteeHotExtendedKey)
-> ByteString -> Either DecoderError (Hash CommitteeHotExtendedKey)
Hash CommitteeHotExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash CommitteeHotExtendedKey -> ByteString
serialiseToCBOR :: Hash CommitteeHotExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash CommitteeHotExtendedKey)
-> ByteString -> Either DecoderError (Hash CommitteeHotExtendedKey)
deserialiseFromCBOR :: AsType (Hash CommitteeHotExtendedKey)
-> ByteString -> Either DecoderError (Hash CommitteeHotExtendedKey)
SerialiseAsCBOR

instance ToCBOR (VerificationKey CommitteeHotExtendedKey) where
  toCBOR :: VerificationKey CommitteeHotExtendedKey -> Encoding
toCBOR (CommitteeHotExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)

instance FromCBOR (VerificationKey CommitteeHotExtendedKey) where
  fromCBOR :: forall s. Decoder s (VerificationKey CommitteeHotExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey CommitteeHotExtendedKey))
-> (XPub -> Decoder s (VerificationKey CommitteeHotExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey CommitteeHotExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey CommitteeHotExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey CommitteeHotExtendedKey
-> Decoder s (VerificationKey CommitteeHotExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey CommitteeHotExtendedKey
 -> Decoder s (VerificationKey CommitteeHotExtendedKey))
-> (XPub -> VerificationKey CommitteeHotExtendedKey)
-> XPub
-> Decoder s (VerificationKey CommitteeHotExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey CommitteeHotExtendedKey
CommitteeHotExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey CommitteeHotExtendedKey) where
  toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding
toCBOR (CommitteeHotExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)

instance FromCBOR (SigningKey CommitteeHotExtendedKey) where
  fromCBOR :: forall s. Decoder s (SigningKey CommitteeHotExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey CommitteeHotExtendedKey))
-> (XPrv -> Decoder s (SigningKey CommitteeHotExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey CommitteeHotExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey CommitteeHotExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey CommitteeHotExtendedKey
-> Decoder s (SigningKey CommitteeHotExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey CommitteeHotExtendedKey
 -> Decoder s (SigningKey CommitteeHotExtendedKey))
-> (XPrv -> SigningKey CommitteeHotExtendedKey)
-> XPrv
-> Decoder s (SigningKey CommitteeHotExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey CommitteeHotExtendedKey
CommitteeHotExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) where
  serialiseToRawBytes :: VerificationKey CommitteeHotExtendedKey -> ByteString
serialiseToRawBytes (CommitteeHotExtendedVerificationKey XPub
xpub) =
    XPub -> ByteString
Crypto.HD.unXPub XPub
xpub

  deserialiseFromRawBytes :: AsType (VerificationKey CommitteeHotExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeHotExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType CommitteeHotExtendedKey
R:AsTypeCommitteeHotExtendedKey
AsCommitteeHotExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey CommitteeHotExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey CommitteeHotExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey CommitteeHotExtendedKey"))
      (XPub -> VerificationKey CommitteeHotExtendedKey
CommitteeHotExtendedVerificationKey (XPub -> VerificationKey CommitteeHotExtendedKey)
-> Either String XPub
-> Either String (VerificationKey CommitteeHotExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)

instance SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) where
  serialiseToRawBytes :: SigningKey CommitteeHotExtendedKey -> ByteString
serialiseToRawBytes (CommitteeHotExtendedSigningKey XPrv
xprv) =
    XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv

  deserialiseFromRawBytes :: AsType (SigningKey CommitteeHotExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (SigningKey CommitteeHotExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType CommitteeHotExtendedKey
R:AsTypeCommitteeHotExtendedKey
AsCommitteeHotExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey CommitteeHotExtendedKey)
-> Either
     SerialiseAsRawBytesError (SigningKey CommitteeHotExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey CommitteeHotExtendedKey"))
      (XPrv -> SigningKey CommitteeHotExtendedKey
CommitteeHotExtendedSigningKey (XPrv -> SigningKey CommitteeHotExtendedKey)
-> Either String XPrv
-> Either String (SigningKey CommitteeHotExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)

instance SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) where
  serialiseToRawBytes :: Hash CommitteeHotExtendedKey -> ByteString
serialiseToRawBytes (CommitteeHotExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash CommitteeHotExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash CommitteeHotExtendedKey)
deserialiseFromRawBytes (AsHash AsType CommitteeHotExtendedKey
R:AsTypeCommitteeHotExtendedKey
AsCommitteeHotExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash CommitteeHotExtendedKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeHotExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash CommitteeHotExtendedKey") (Maybe (Hash CommitteeHotExtendedKey)
 -> Either SerialiseAsRawBytesError (Hash CommitteeHotExtendedKey))
-> Maybe (Hash CommitteeHotExtendedKey)
-> Either SerialiseAsRawBytesError (Hash CommitteeHotExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'HotCommitteeRole -> Hash CommitteeHotExtendedKey
CommitteeHotExtendedKeyHash (KeyHash 'HotCommitteeRole -> Hash CommitteeHotExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'HotCommitteeRole)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash CommitteeHotExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'HotCommitteeRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash CommitteeHotExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash CommitteeHotExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) where
  textEnvelopeType :: AsType (VerificationKey CommitteeHotExtendedKey)
-> TextEnvelopeType
textEnvelopeType AsType (VerificationKey CommitteeHotExtendedKey)
_ = TextEnvelopeType
"ConstitutionalCommitteeHotExtendedVerificationKey_ed25519_bip32"

instance HasTextEnvelope (SigningKey CommitteeHotExtendedKey) where
  textEnvelopeType :: AsType (SigningKey CommitteeHotExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey CommitteeHotExtendedKey)
_ = TextEnvelopeType
"ConstitutionalCommitteeHotExtendedSigningKey_ed25519_bip32"

instance SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) where
  bech32PrefixFor :: VerificationKey CommitteeHotExtendedKey -> Text
bech32PrefixFor VerificationKey CommitteeHotExtendedKey
_ = Text
"cc_hot_xvk"
  bech32PrefixesPermitted :: AsType (VerificationKey CommitteeHotExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey CommitteeHotExtendedKey)
_ = [Text
"cc_hot_xvk"]

instance SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) where
  bech32PrefixFor :: SigningKey CommitteeHotExtendedKey -> Text
bech32PrefixFor SigningKey CommitteeHotExtendedKey
_ = Text
"cc_hot_xsk"
  bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey CommitteeHotExtendedKey)
_ = [Text
"cc_hot_xsk"]

instance CastVerificationKeyRole CommitteeHotExtendedKey CommitteeHotKey where
  castVerificationKey :: VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotKey
castVerificationKey (CommitteeHotExtendedVerificationKey XPub
vk) =
    VKey 'HotCommitteeRole -> VerificationKey CommitteeHotKey
CommitteeHotVerificationKey
      (VKey 'HotCommitteeRole -> VerificationKey CommitteeHotKey)
-> (XPub -> VKey 'HotCommitteeRole)
-> XPub
-> VerificationKey CommitteeHotKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'HotCommitteeRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'HotCommitteeRole)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'HotCommitteeRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey CommitteeHotKey)
-> XPub -> VerificationKey CommitteeHotKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey (CommitteeHot): byron and shelley key sizes do not match!"

--
-- Shelley genesis extended ed25519 keys
--

-- | Shelley-era genesis keys using extended ed25519 cryptographic keys.
--
-- These serve the same role as normal genesis keys, but are here to support
-- legacy Byron genesis keys which used extended keys.
--
-- The extended verification keys can be converted (via 'castVerificationKey')
-- to ordinary keys (i.e. 'VerificationKey' 'GenesisKey') but this is /not/ the
-- case for the signing keys. The signing keys can be used to witness
-- transactions directly, with verification via their non-extended verification
-- key ('VerificationKey' 'GenesisKey').
--
-- This is a type level tag, used with other interfaces like 'Key'.
data GenesisExtendedKey

instance HasTypeProxy GenesisExtendedKey where
  data AsType GenesisExtendedKey = AsGenesisExtendedKey
  proxyToAsType :: Proxy GenesisExtendedKey -> AsType GenesisExtendedKey
proxyToAsType Proxy GenesisExtendedKey
_ = AsType GenesisExtendedKey
AsGenesisExtendedKey

instance Key GenesisExtendedKey where
  newtype VerificationKey GenesisExtendedKey
    = GenesisExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
(VerificationKey GenesisExtendedKey
 -> VerificationKey GenesisExtendedKey -> Bool)
-> (VerificationKey GenesisExtendedKey
    -> VerificationKey GenesisExtendedKey -> Bool)
-> Eq (VerificationKey GenesisExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
== :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
$c/= :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
/= :: VerificationKey GenesisExtendedKey
-> VerificationKey GenesisExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey GenesisExtendedKey)
HasTypeProxy (VerificationKey GenesisExtendedKey) =>
(VerificationKey GenesisExtendedKey -> ByteString)
-> (AsType (VerificationKey GenesisExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey GenesisExtendedKey))
-> SerialiseAsCBOR (VerificationKey GenesisExtendedKey)
AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey)
VerificationKey GenesisExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey GenesisExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey GenesisExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey GenesisExtendedKey -> ShowS
[VerificationKey GenesisExtendedKey] -> ShowS
VerificationKey GenesisExtendedKey -> String
(Int -> VerificationKey GenesisExtendedKey -> ShowS)
-> (VerificationKey GenesisExtendedKey -> String)
-> ([VerificationKey GenesisExtendedKey] -> ShowS)
-> Show (VerificationKey GenesisExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS
$cshow :: VerificationKey GenesisExtendedKey -> String
show :: VerificationKey GenesisExtendedKey -> String
$cshowList :: [VerificationKey GenesisExtendedKey] -> ShowS
showList :: [VerificationKey GenesisExtendedKey] -> ShowS
Show, String -> VerificationKey GenesisExtendedKey
(String -> VerificationKey GenesisExtendedKey)
-> IsString (VerificationKey GenesisExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey GenesisExtendedKey
fromString :: String -> VerificationKey GenesisExtendedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisExtendedKey)

  newtype SigningKey GenesisExtendedKey
    = GenesisExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey GenesisExtendedKey)
HasTypeProxy (SigningKey GenesisExtendedKey) =>
(SigningKey GenesisExtendedKey -> ByteString)
-> (AsType (SigningKey GenesisExtendedKey)
    -> ByteString
    -> Either DecoderError (SigningKey GenesisExtendedKey))
-> SerialiseAsCBOR (SigningKey GenesisExtendedKey)
AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey)
SigningKey GenesisExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey GenesisExtendedKey -> ByteString
serialiseToCBOR :: SigningKey GenesisExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey GenesisExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey GenesisExtendedKey -> ShowS
[SigningKey GenesisExtendedKey] -> ShowS
SigningKey GenesisExtendedKey -> String
(Int -> SigningKey GenesisExtendedKey -> ShowS)
-> (SigningKey GenesisExtendedKey -> String)
-> ([SigningKey GenesisExtendedKey] -> ShowS)
-> Show (SigningKey GenesisExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS
showsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS
$cshow :: SigningKey GenesisExtendedKey -> String
show :: SigningKey GenesisExtendedKey -> String
$cshowList :: [SigningKey GenesisExtendedKey] -> ShowS
showList :: [SigningKey GenesisExtendedKey] -> ShowS
Show, String -> SigningKey GenesisExtendedKey
(String -> SigningKey GenesisExtendedKey)
-> IsString (SigningKey GenesisExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey GenesisExtendedKey
fromString :: 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
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word
deterministicSigningKeySeedSize AsType GenesisExtendedKey
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
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey GenesisExtendedKey
    -> Hash GenesisExtendedKey
  verificationKeyHash :: VerificationKey GenesisExtendedKey -> Hash GenesisExtendedKey
verificationKeyHash (GenesisExtendedVerificationKey XPub
vk) =
    KeyHash 'Staking -> Hash GenesisExtendedKey
GenesisExtendedKeyHash
      (KeyHash 'Staking -> Hash GenesisExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'Staking)
-> Hash ADDRHASH XPub
-> Hash GenesisExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'Staking
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash GenesisExtendedKey)
-> Hash ADDRHASH XPub -> Hash GenesisExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

instance ToCBOR (VerificationKey GenesisExtendedKey) where
  toCBOR :: VerificationKey GenesisExtendedKey -> Encoding
toCBOR (GenesisExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey GenesisExtendedKey))
-> (XPub -> Decoder s (VerificationKey GenesisExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey GenesisExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey GenesisExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey GenesisExtendedKey
-> Decoder s (VerificationKey GenesisExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey GenesisExtendedKey
 -> Decoder s (VerificationKey GenesisExtendedKey))
-> (XPub -> VerificationKey GenesisExtendedKey)
-> XPub
-> Decoder s (VerificationKey GenesisExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey GenesisExtendedKey) where
  toCBOR :: SigningKey GenesisExtendedKey -> Encoding
toCBOR (GenesisExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey GenesisExtendedKey))
-> (XPrv -> Decoder s (SigningKey GenesisExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey GenesisExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey GenesisExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey GenesisExtendedKey
-> Decoder s (SigningKey GenesisExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey GenesisExtendedKey
 -> Decoder s (SigningKey GenesisExtendedKey))
-> (XPrv -> SigningKey GenesisExtendedKey)
-> XPrv
-> Decoder s (SigningKey GenesisExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) where
  serialiseToRawBytes :: VerificationKey GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedVerificationKey XPub
xpub) =
    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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey GenesisExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey GenesisExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisExtendedKey")) (Either String (VerificationKey GenesisExtendedKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey GenesisExtendedKey))
-> Either String (VerificationKey GenesisExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey GenesisExtendedKey)
forall a b. (a -> b) -> a -> b
$
      XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey (XPub -> VerificationKey GenesisExtendedKey)
-> Either String XPub
-> Either String (VerificationKey GenesisExtendedKey)
forall (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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey GenesisExtendedKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg))
      (Either String (SigningKey GenesisExtendedKey)
 -> Either SerialiseAsRawBytesError (SigningKey GenesisExtendedKey))
-> Either String (SigningKey GenesisExtendedKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey (XPrv -> SigningKey GenesisExtendedKey)
-> Either String XPrv
-> Either String (SigningKey GenesisExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs

newtype instance Hash GenesisExtendedKey
  = GenesisExtendedKeyHash
  {Hash GenesisExtendedKey -> KeyHash 'Staking
unGenesisExtendedKeyHash :: Shelley.KeyHash Shelley.Staking}
  deriving stock (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
(Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> Eq (Hash GenesisExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
== :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$c/= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
/= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
Eq, Eq (Hash GenesisExtendedKey)
Eq (Hash GenesisExtendedKey) =>
(Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool)
-> (Hash GenesisExtendedKey
    -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey)
-> (Hash GenesisExtendedKey
    -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey)
-> Ord (Hash GenesisExtendedKey)
Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering
Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering
compare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering
$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
>= :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool
$cmax :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
max :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
$cmin :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
min :: Hash GenesisExtendedKey
-> Hash GenesisExtendedKey -> Hash GenesisExtendedKey
Ord)
  deriving (Int -> Hash GenesisExtendedKey -> ShowS
[Hash GenesisExtendedKey] -> ShowS
Hash GenesisExtendedKey -> String
(Int -> Hash GenesisExtendedKey -> ShowS)
-> (Hash GenesisExtendedKey -> String)
-> ([Hash GenesisExtendedKey] -> ShowS)
-> Show (Hash GenesisExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash GenesisExtendedKey -> ShowS
showsPrec :: Int -> Hash GenesisExtendedKey -> ShowS
$cshow :: Hash GenesisExtendedKey -> String
show :: Hash GenesisExtendedKey -> String
$cshowList :: [Hash GenesisExtendedKey] -> ShowS
showList :: [Hash GenesisExtendedKey] -> ShowS
Show, String -> Hash GenesisExtendedKey
(String -> Hash GenesisExtendedKey)
-> IsString (Hash GenesisExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash GenesisExtendedKey
fromString :: String -> Hash GenesisExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisExtendedKey)
  deriving (Typeable (Hash GenesisExtendedKey)
Typeable (Hash GenesisExtendedKey) =>
(Hash GenesisExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash GenesisExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash GenesisExtendedKey] -> Size)
-> ToCBOR (Hash GenesisExtendedKey)
Hash GenesisExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash GenesisExtendedKey -> Encoding
toCBOR :: Hash GenesisExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisExtendedKey] -> Size
ToCBOR, Typeable (Hash GenesisExtendedKey)
Typeable (Hash GenesisExtendedKey) =>
(forall s. Decoder s (Hash GenesisExtendedKey))
-> (Proxy (Hash GenesisExtendedKey) -> Text)
-> FromCBOR (Hash GenesisExtendedKey)
Proxy (Hash GenesisExtendedKey) -> Text
forall s. Decoder s (Hash GenesisExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash GenesisExtendedKey)
fromCBOR :: forall s. Decoder s (Hash GenesisExtendedKey)
$clabel :: Proxy (Hash GenesisExtendedKey) -> Text
label :: Proxy (Hash GenesisExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash GenesisExtendedKey)
  deriving anyclass HasTypeProxy (Hash GenesisExtendedKey)
HasTypeProxy (Hash GenesisExtendedKey) =>
(Hash GenesisExtendedKey -> ByteString)
-> (AsType (Hash GenesisExtendedKey)
    -> ByteString -> Either DecoderError (Hash GenesisExtendedKey))
-> SerialiseAsCBOR (Hash GenesisExtendedKey)
AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey)
Hash GenesisExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash GenesisExtendedKey -> ByteString
serialiseToCBOR :: Hash GenesisExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey)
deserialiseFromCBOR :: AsType (Hash GenesisExtendedKey)
-> ByteString -> Either DecoderError (Hash GenesisExtendedKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash GenesisExtendedKey) where
  serialiseToRawBytes :: Hash GenesisExtendedKey -> ByteString
serialiseToRawBytes (GenesisExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash GenesisExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash GenesisExtendedKey)
deserialiseFromRawBytes (AsHash AsType GenesisExtendedKey
R:AsTypeGenesisExtendedKey
AsGenesisExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash GenesisExtendedKey)
-> Either SerialiseAsRawBytesError (Hash GenesisExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisExtendedKey") (Maybe (Hash GenesisExtendedKey)
 -> Either SerialiseAsRawBytesError (Hash GenesisExtendedKey))
-> Maybe (Hash GenesisExtendedKey)
-> Either SerialiseAsRawBytesError (Hash GenesisExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Staking -> Hash GenesisExtendedKey
GenesisExtendedKeyHash (KeyHash 'Staking -> Hash GenesisExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash GenesisExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash GenesisExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash GenesisExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
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 -> VerificationKey GenesisKey
GenesisVerificationKey
      (VKey 'Genesis -> VerificationKey GenesisKey)
-> (XPub -> VKey 'Genesis) -> XPub -> VerificationKey GenesisKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Genesis
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'Genesis)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'Genesis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey GenesisKey)
-> XPub -> VerificationKey GenesisKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley key sizes do not match!"

--
-- Genesis delegate keys
--

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)
    deriving stock VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
(VerificationKey GenesisDelegateKey
 -> VerificationKey GenesisDelegateKey -> Bool)
-> (VerificationKey GenesisDelegateKey
    -> VerificationKey GenesisDelegateKey -> Bool)
-> Eq (VerificationKey GenesisDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
== :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
$c/= :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
/= :: VerificationKey GenesisDelegateKey
-> VerificationKey GenesisDelegateKey -> Bool
Eq
    deriving (Int -> VerificationKey GenesisDelegateKey -> ShowS
[VerificationKey GenesisDelegateKey] -> ShowS
VerificationKey GenesisDelegateKey -> String
(Int -> VerificationKey GenesisDelegateKey -> ShowS)
-> (VerificationKey GenesisDelegateKey -> String)
-> ([VerificationKey GenesisDelegateKey] -> ShowS)
-> Show (VerificationKey GenesisDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS
showsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS
$cshow :: VerificationKey GenesisDelegateKey -> String
show :: VerificationKey GenesisDelegateKey -> String
$cshowList :: [VerificationKey GenesisDelegateKey] -> ShowS
showList :: [VerificationKey GenesisDelegateKey] -> ShowS
Show, String -> VerificationKey GenesisDelegateKey
(String -> VerificationKey GenesisDelegateKey)
-> IsString (VerificationKey GenesisDelegateKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey GenesisDelegateKey
fromString :: String -> VerificationKey GenesisDelegateKey
IsString) via UsingRawBytesHex (VerificationKey GenesisDelegateKey)
    deriving newtype (Typeable (VerificationKey GenesisDelegateKey)
Typeable (VerificationKey GenesisDelegateKey) =>
(VerificationKey GenesisDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey GenesisDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey GenesisDelegateKey] -> Size)
-> ToCBOR (VerificationKey GenesisDelegateKey)
VerificationKey GenesisDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VerificationKey GenesisDelegateKey -> Encoding
toCBOR :: VerificationKey GenesisDelegateKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisDelegateKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisDelegateKey] -> Size
ToCBOR, Typeable (VerificationKey GenesisDelegateKey)
Typeable (VerificationKey GenesisDelegateKey) =>
(forall s. Decoder s (VerificationKey GenesisDelegateKey))
-> (Proxy (VerificationKey GenesisDelegateKey) -> Text)
-> FromCBOR (VerificationKey GenesisDelegateKey)
Proxy (VerificationKey GenesisDelegateKey) -> Text
forall s. Decoder s (VerificationKey GenesisDelegateKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisDelegateKey)
fromCBOR :: forall s. Decoder s (VerificationKey GenesisDelegateKey)
$clabel :: Proxy (VerificationKey GenesisDelegateKey) -> Text
label :: Proxy (VerificationKey GenesisDelegateKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey GenesisDelegateKey)
HasTypeProxy (VerificationKey GenesisDelegateKey) =>
(VerificationKey GenesisDelegateKey -> ByteString)
-> (AsType (VerificationKey GenesisDelegateKey)
    -> ByteString
    -> Either DecoderError (VerificationKey GenesisDelegateKey))
-> SerialiseAsCBOR (VerificationKey GenesisDelegateKey)
AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey)
VerificationKey GenesisDelegateKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey GenesisDelegateKey -> ByteString
serialiseToCBOR :: VerificationKey GenesisDelegateKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey)
deserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateKey)
SerialiseAsCBOR

  newtype SigningKey GenesisDelegateKey
    = GenesisDelegateSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey GenesisDelegateKey -> ShowS
[SigningKey GenesisDelegateKey] -> ShowS
SigningKey GenesisDelegateKey -> String
(Int -> SigningKey GenesisDelegateKey -> ShowS)
-> (SigningKey GenesisDelegateKey -> String)
-> ([SigningKey GenesisDelegateKey] -> ShowS)
-> Show (SigningKey GenesisDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS
showsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS
$cshow :: SigningKey GenesisDelegateKey -> String
show :: SigningKey GenesisDelegateKey -> String
$cshowList :: [SigningKey GenesisDelegateKey] -> ShowS
showList :: [SigningKey GenesisDelegateKey] -> ShowS
Show, String -> SigningKey GenesisDelegateKey
(String -> SigningKey GenesisDelegateKey)
-> IsString (SigningKey GenesisDelegateKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey GenesisDelegateKey
fromString :: String -> SigningKey GenesisDelegateKey
IsString) via UsingRawBytesHex (SigningKey GenesisDelegateKey)
    deriving newtype (Typeable (SigningKey GenesisDelegateKey)
Typeable (SigningKey GenesisDelegateKey) =>
(SigningKey GenesisDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey GenesisDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey GenesisDelegateKey] -> Size)
-> ToCBOR (SigningKey GenesisDelegateKey)
SigningKey GenesisDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SigningKey GenesisDelegateKey -> Encoding
toCBOR :: SigningKey GenesisDelegateKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisDelegateKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisDelegateKey] -> Size
ToCBOR, Typeable (SigningKey GenesisDelegateKey)
Typeable (SigningKey GenesisDelegateKey) =>
(forall s. Decoder s (SigningKey GenesisDelegateKey))
-> (Proxy (SigningKey GenesisDelegateKey) -> Text)
-> FromCBOR (SigningKey GenesisDelegateKey)
Proxy (SigningKey GenesisDelegateKey) -> Text
forall s. Decoder s (SigningKey GenesisDelegateKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisDelegateKey)
fromCBOR :: forall s. Decoder s (SigningKey GenesisDelegateKey)
$clabel :: Proxy (SigningKey GenesisDelegateKey) -> Text
label :: Proxy (SigningKey GenesisDelegateKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey GenesisDelegateKey)
HasTypeProxy (SigningKey GenesisDelegateKey) =>
(SigningKey GenesisDelegateKey -> ByteString)
-> (AsType (SigningKey GenesisDelegateKey)
    -> ByteString
    -> Either DecoderError (SigningKey GenesisDelegateKey))
-> SerialiseAsCBOR (SigningKey GenesisDelegateKey)
AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey)
SigningKey GenesisDelegateKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey GenesisDelegateKey -> ByteString
serialiseToCBOR :: SigningKey GenesisDelegateKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey)
deserialiseFromCBOR :: AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType GenesisDelegateKey -> Crypto.Seed -> SigningKey GenesisDelegateKey
  deterministicSigningKey :: AsType GenesisDelegateKey -> Seed -> SigningKey GenesisDelegateKey
deterministicSigningKey AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey GenesisDelegateKey
GenesisDelegateSigningKey (Seed -> SignKeyDSIGN DSIGN
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 =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey
  getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey
getVerificationKey (GenesisDelegateSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'GenesisDelegate -> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey (VerKeyDSIGN DSIGN -> VKey 'GenesisDelegate
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey
  verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey
verificationKeyHash (GenesisDelegateVerificationKey VKey 'GenesisDelegate
vkey) =
    KeyHash 'GenesisDelegate -> Hash GenesisDelegateKey
GenesisDelegateKeyHash (VKey 'GenesisDelegate -> KeyHash 'GenesisDelegate
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'GenesisDelegate
vkey)

instance SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) where
  serialiseToRawBytes :: VerificationKey GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey GenesisDelegateKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey GenesisDelegateKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey GenesisDelegateKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey GenesisDelegateKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisDelegateKey") (Maybe (VerificationKey GenesisDelegateKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey GenesisDelegateKey))
-> Maybe (VerificationKey GenesisDelegateKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey GenesisDelegateKey)
forall a b. (a -> b) -> a -> b
$
      VKey 'GenesisDelegate -> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey (VKey 'GenesisDelegate -> VerificationKey GenesisDelegateKey)
-> (VerKeyDSIGN DSIGN -> VKey 'GenesisDelegate)
-> VerKeyDSIGN DSIGN
-> VerificationKey GenesisDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'GenesisDelegate
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey GenesisDelegateKey)
-> Maybe (VerKeyDSIGN DSIGN)
-> Maybe (VerificationKey GenesisDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey GenesisDelegateKey) where
  serialiseToRawBytes :: SigningKey GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey GenesisDelegateKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisDelegateKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (SigningKey GenesisDelegateKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisDelegateKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey GenesisDelegateKey") (Maybe (SigningKey GenesisDelegateKey)
 -> Either SerialiseAsRawBytesError (SigningKey GenesisDelegateKey))
-> Maybe (SigningKey GenesisDelegateKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisDelegateKey)
forall a b. (a -> b) -> a -> b
$
      SignKeyDSIGN DSIGN -> SigningKey GenesisDelegateKey
GenesisDelegateSigningKey (SignKeyDSIGN DSIGN -> SigningKey GenesisDelegateKey)
-> Maybe (SignKeyDSIGN DSIGN)
-> Maybe (SigningKey GenesisDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs

newtype instance Hash GenesisDelegateKey
  = GenesisDelegateKeyHash
  {Hash GenesisDelegateKey -> KeyHash 'GenesisDelegate
unGenesisDelegateKeyHash :: Shelley.KeyHash Shelley.GenesisDelegate}
  deriving stock (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
(Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> Eq (Hash GenesisDelegateKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
== :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$c/= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
/= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
Eq, Eq (Hash GenesisDelegateKey)
Eq (Hash GenesisDelegateKey) =>
(Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool)
-> (Hash GenesisDelegateKey
    -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey)
-> (Hash GenesisDelegateKey
    -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey)
-> Ord (Hash GenesisDelegateKey)
Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering
Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering
compare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering
$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
>= :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool
$cmax :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
max :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
$cmin :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
min :: Hash GenesisDelegateKey
-> Hash GenesisDelegateKey -> Hash GenesisDelegateKey
Ord)
  deriving (Int -> Hash GenesisDelegateKey -> ShowS
[Hash GenesisDelegateKey] -> ShowS
Hash GenesisDelegateKey -> String
(Int -> Hash GenesisDelegateKey -> ShowS)
-> (Hash GenesisDelegateKey -> String)
-> ([Hash GenesisDelegateKey] -> ShowS)
-> Show (Hash GenesisDelegateKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash GenesisDelegateKey -> ShowS
showsPrec :: Int -> Hash GenesisDelegateKey -> ShowS
$cshow :: Hash GenesisDelegateKey -> String
show :: Hash GenesisDelegateKey -> String
$cshowList :: [Hash GenesisDelegateKey] -> ShowS
showList :: [Hash GenesisDelegateKey] -> ShowS
Show, String -> Hash GenesisDelegateKey
(String -> Hash GenesisDelegateKey)
-> IsString (Hash GenesisDelegateKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash GenesisDelegateKey
fromString :: String -> Hash GenesisDelegateKey
IsString) via UsingRawBytesHex (Hash GenesisDelegateKey)
  deriving (Typeable (Hash GenesisDelegateKey)
Typeable (Hash GenesisDelegateKey) =>
(Hash GenesisDelegateKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash GenesisDelegateKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash GenesisDelegateKey] -> Size)
-> ToCBOR (Hash GenesisDelegateKey)
Hash GenesisDelegateKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash GenesisDelegateKey -> Encoding
toCBOR :: Hash GenesisDelegateKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateKey] -> Size
ToCBOR, Typeable (Hash GenesisDelegateKey)
Typeable (Hash GenesisDelegateKey) =>
(forall s. Decoder s (Hash GenesisDelegateKey))
-> (Proxy (Hash GenesisDelegateKey) -> Text)
-> FromCBOR (Hash GenesisDelegateKey)
Proxy (Hash GenesisDelegateKey) -> Text
forall s. Decoder s (Hash GenesisDelegateKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash GenesisDelegateKey)
fromCBOR :: forall s. Decoder s (Hash GenesisDelegateKey)
$clabel :: Proxy (Hash GenesisDelegateKey) -> Text
label :: Proxy (Hash GenesisDelegateKey) -> Text
FromCBOR) via UsingRawBytes (Hash GenesisDelegateKey)
  deriving anyclass HasTypeProxy (Hash GenesisDelegateKey)
HasTypeProxy (Hash GenesisDelegateKey) =>
(Hash GenesisDelegateKey -> ByteString)
-> (AsType (Hash GenesisDelegateKey)
    -> ByteString -> Either DecoderError (Hash GenesisDelegateKey))
-> SerialiseAsCBOR (Hash GenesisDelegateKey)
AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey)
Hash GenesisDelegateKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash GenesisDelegateKey -> ByteString
serialiseToCBOR :: Hash GenesisDelegateKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey)
deserialiseFromCBOR :: AsType (Hash GenesisDelegateKey)
-> ByteString -> Either DecoderError (Hash GenesisDelegateKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash GenesisDelegateKey) where
  serialiseToRawBytes :: Hash GenesisDelegateKey -> ByteString
serialiseToRawBytes (GenesisDelegateKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash GenesisDelegateKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash GenesisDelegateKey)
deserialiseFromRawBytes (AsHash AsType GenesisDelegateKey
R:AsTypeGenesisDelegateKey
AsGenesisDelegateKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash GenesisDelegateKey)
-> Either SerialiseAsRawBytesError (Hash GenesisDelegateKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisDelegateKey") (Maybe (Hash GenesisDelegateKey)
 -> Either SerialiseAsRawBytesError (Hash GenesisDelegateKey))
-> Maybe (Hash GenesisDelegateKey)
-> Either SerialiseAsRawBytesError (Hash GenesisDelegateKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'GenesisDelegate -> Hash GenesisDelegateKey
GenesisDelegateKeyHash (KeyHash 'GenesisDelegate -> Hash GenesisDelegateKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'GenesisDelegate)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash GenesisDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'GenesisDelegate
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash GenesisDelegateKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash GenesisDelegateKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey GenesisDelegateKey) where
  textEnvelopeType :: AsType (VerificationKey GenesisDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisDelegateKey)
_ =
    TextEnvelopeType
"GenesisDelegateVerificationKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey GenesisDelegateKey) where
  textEnvelopeType :: AsType (SigningKey GenesisDelegateKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisDelegateKey)
_ =
    TextEnvelopeType
"GenesisDelegateSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance CastVerificationKeyRole GenesisDelegateKey StakePoolKey where
  castVerificationKey :: VerificationKey GenesisDelegateKey -> VerificationKey StakePoolKey
castVerificationKey (GenesisDelegateVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vkey)) =
    VKey 'StakePool -> VerificationKey StakePoolKey
StakePoolVerificationKey (VerKeyDSIGN DSIGN -> VKey 'StakePool
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey VerKeyDSIGN DSIGN
vkey)

instance CastSigningKeyRole GenesisDelegateKey StakePoolKey where
  castSigningKey :: SigningKey GenesisDelegateKey -> SigningKey StakePoolKey
castSigningKey (GenesisDelegateSigningKey SignKeyDSIGN DSIGN
skey) =
    SignKeyDSIGN DSIGN -> SigningKey StakePoolKey
StakePoolSigningKey SignKeyDSIGN DSIGN
skey

instance CastVerificationKeyRole StakePoolKey StakeKey where
  castVerificationKey :: VerificationKey StakePoolKey -> VerificationKey StakeKey
castVerificationKey (StakePoolVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vkey)) =
    VKey 'Staking -> VerificationKey StakeKey
StakeVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Staking
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey VerKeyDSIGN DSIGN
vkey)

--
-- Shelley genesis delegate extended ed25519 keys
--

-- | Shelley-era genesis keys using extended ed25519 cryptographic keys.
--
-- These serve the same role as normal genesis keys, but are here to support
-- legacy Byron genesis keys which used extended keys.
--
-- The extended verification keys can be converted (via 'castVerificationKey')
-- to ordinary keys (i.e. 'VerificationKey' 'GenesisKey') but this is /not/ the
-- case for the signing keys. The signing keys can be used to witness
-- transactions directly, with verification via their non-extended verification
-- key ('VerificationKey' 'GenesisKey').
--
-- This is a type level tag, used with other interfaces like 'Key'.
data GenesisDelegateExtendedKey

instance HasTypeProxy GenesisDelegateExtendedKey where
  data AsType GenesisDelegateExtendedKey = AsGenesisDelegateExtendedKey
  proxyToAsType :: Proxy GenesisDelegateExtendedKey
-> AsType GenesisDelegateExtendedKey
proxyToAsType Proxy GenesisDelegateExtendedKey
_ = AsType GenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey

instance Key GenesisDelegateExtendedKey where
  newtype VerificationKey GenesisDelegateExtendedKey
    = GenesisDelegateExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
(VerificationKey GenesisDelegateExtendedKey
 -> VerificationKey GenesisDelegateExtendedKey -> Bool)
-> (VerificationKey GenesisDelegateExtendedKey
    -> VerificationKey GenesisDelegateExtendedKey -> Bool)
-> Eq (VerificationKey GenesisDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
== :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
$c/= :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
/= :: VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey GenesisDelegateExtendedKey)
HasTypeProxy (VerificationKey GenesisDelegateExtendedKey) =>
(VerificationKey GenesisDelegateExtendedKey -> ByteString)
-> (AsType (VerificationKey GenesisDelegateExtendedKey)
    -> ByteString
    -> Either
         DecoderError (VerificationKey GenesisDelegateExtendedKey))
-> SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey)
AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateExtendedKey)
VerificationKey GenesisDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey GenesisDelegateExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey GenesisDelegateExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisDelegateExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
[VerificationKey GenesisDelegateExtendedKey] -> ShowS
VerificationKey GenesisDelegateExtendedKey -> String
(Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS)
-> (VerificationKey GenesisDelegateExtendedKey -> String)
-> ([VerificationKey GenesisDelegateExtendedKey] -> ShowS)
-> Show (VerificationKey GenesisDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS
$cshow :: VerificationKey GenesisDelegateExtendedKey -> String
show :: VerificationKey GenesisDelegateExtendedKey -> String
$cshowList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS
showList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS
Show, String -> VerificationKey GenesisDelegateExtendedKey
(String -> VerificationKey GenesisDelegateExtendedKey)
-> IsString (VerificationKey GenesisDelegateExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey GenesisDelegateExtendedKey
fromString :: String -> VerificationKey GenesisDelegateExtendedKey
IsString) via UsingRawBytesHex (VerificationKey GenesisDelegateExtendedKey)

  newtype SigningKey GenesisDelegateExtendedKey
    = GenesisDelegateExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey GenesisDelegateExtendedKey)
HasTypeProxy (SigningKey GenesisDelegateExtendedKey) =>
(SigningKey GenesisDelegateExtendedKey -> ByteString)
-> (AsType (SigningKey GenesisDelegateExtendedKey)
    -> ByteString
    -> Either DecoderError (SigningKey GenesisDelegateExtendedKey))
-> SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey)
AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey)
SigningKey GenesisDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey GenesisDelegateExtendedKey -> ByteString
serialiseToCBOR :: SigningKey GenesisDelegateExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey GenesisDelegateExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
[SigningKey GenesisDelegateExtendedKey] -> ShowS
SigningKey GenesisDelegateExtendedKey -> String
(Int -> SigningKey GenesisDelegateExtendedKey -> ShowS)
-> (SigningKey GenesisDelegateExtendedKey -> String)
-> ([SigningKey GenesisDelegateExtendedKey] -> ShowS)
-> Show (SigningKey GenesisDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
showsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS
$cshow :: SigningKey GenesisDelegateExtendedKey -> String
show :: SigningKey GenesisDelegateExtendedKey -> String
$cshowList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS
showList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS
Show, String -> SigningKey GenesisDelegateExtendedKey
(String -> SigningKey GenesisDelegateExtendedKey)
-> IsString (SigningKey GenesisDelegateExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey GenesisDelegateExtendedKey
fromString :: 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
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word
deterministicSigningKeySeedSize AsType GenesisDelegateExtendedKey
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
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey
  verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
verificationKeyHash (GenesisDelegateExtendedVerificationKey XPub
vk) =
    KeyHash 'Staking -> Hash GenesisDelegateExtendedKey
GenesisDelegateExtendedKeyHash
      (KeyHash 'Staking -> Hash GenesisDelegateExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'Staking)
-> Hash ADDRHASH XPub
-> Hash GenesisDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'Staking
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash GenesisDelegateExtendedKey)
-> Hash ADDRHASH XPub -> Hash GenesisDelegateExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

instance ToCBOR (VerificationKey GenesisDelegateExtendedKey) where
  toCBOR :: VerificationKey GenesisDelegateExtendedKey -> Encoding
toCBOR (GenesisDelegateExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey GenesisDelegateExtendedKey))
-> (XPub -> Decoder s (VerificationKey GenesisDelegateExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey GenesisDelegateExtendedKey
-> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey GenesisDelegateExtendedKey
 -> Decoder s (VerificationKey GenesisDelegateExtendedKey))
-> (XPub -> VerificationKey GenesisDelegateExtendedKey)
-> XPub
-> Decoder s (VerificationKey GenesisDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey GenesisDelegateExtendedKey) where
  toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding
toCBOR (GenesisDelegateExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
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 <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey GenesisDelegateExtendedKey))
-> (XPrv -> Decoder s (SigningKey GenesisDelegateExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey GenesisDelegateExtendedKey
-> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey GenesisDelegateExtendedKey
 -> Decoder s (SigningKey GenesisDelegateExtendedKey))
-> (XPrv -> SigningKey GenesisDelegateExtendedKey)
-> XPrv
-> Decoder s (SigningKey GenesisDelegateExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) where
  serialiseToRawBytes :: VerificationKey GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedVerificationKey XPub
xpub) =
    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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey GenesisDelegateExtendedKey)
-> Either
     SerialiseAsRawBytesError
     (VerificationKey GenesisDelegateExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg)
      )
      (Either String (VerificationKey GenesisDelegateExtendedKey)
 -> Either
      SerialiseAsRawBytesError
      (VerificationKey GenesisDelegateExtendedKey))
-> Either String (VerificationKey GenesisDelegateExtendedKey)
-> Either
     SerialiseAsRawBytesError
     (VerificationKey GenesisDelegateExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey (XPub -> VerificationKey GenesisDelegateExtendedKey)
-> Either String XPub
-> Either String (VerificationKey GenesisDelegateExtendedKey)
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 =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey GenesisDelegateExtendedKey)
-> Either
     SerialiseAsRawBytesError (SigningKey GenesisDelegateExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg)
      )
      (Either String (SigningKey GenesisDelegateExtendedKey)
 -> Either
      SerialiseAsRawBytesError (SigningKey GenesisDelegateExtendedKey))
-> Either String (SigningKey GenesisDelegateExtendedKey)
-> Either
     SerialiseAsRawBytesError (SigningKey GenesisDelegateExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey (XPrv -> SigningKey GenesisDelegateExtendedKey)
-> Either String XPrv
-> Either String (SigningKey GenesisDelegateExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs

newtype instance Hash GenesisDelegateExtendedKey
  = GenesisDelegateExtendedKeyHash
  {Hash GenesisDelegateExtendedKey -> KeyHash 'Staking
unGenesisDelegateExtendedKeyHash :: Shelley.KeyHash Shelley.Staking}
  deriving stock (Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
(Hash GenesisDelegateExtendedKey
 -> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey -> Bool)
-> Eq (Hash GenesisDelegateExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
== :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$c/= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
/= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
Eq, Eq (Hash GenesisDelegateExtendedKey)
Eq (Hash GenesisDelegateExtendedKey) =>
(Hash GenesisDelegateExtendedKey
 -> Hash GenesisDelegateExtendedKey -> Ordering)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey -> Bool)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey)
-> (Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey
    -> Hash GenesisDelegateExtendedKey)
-> Ord (Hash GenesisDelegateExtendedKey)
Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering
Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering
compare :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Ordering
$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
>= :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey -> Bool
$cmax :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
max :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
$cmin :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
min :: Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
-> Hash GenesisDelegateExtendedKey
Ord)
  deriving (Int -> Hash GenesisDelegateExtendedKey -> ShowS
[Hash GenesisDelegateExtendedKey] -> ShowS
Hash GenesisDelegateExtendedKey -> String
(Int -> Hash GenesisDelegateExtendedKey -> ShowS)
-> (Hash GenesisDelegateExtendedKey -> String)
-> ([Hash GenesisDelegateExtendedKey] -> ShowS)
-> Show (Hash GenesisDelegateExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash GenesisDelegateExtendedKey -> ShowS
showsPrec :: Int -> Hash GenesisDelegateExtendedKey -> ShowS
$cshow :: Hash GenesisDelegateExtendedKey -> String
show :: Hash GenesisDelegateExtendedKey -> String
$cshowList :: [Hash GenesisDelegateExtendedKey] -> ShowS
showList :: [Hash GenesisDelegateExtendedKey] -> ShowS
Show, String -> Hash GenesisDelegateExtendedKey
(String -> Hash GenesisDelegateExtendedKey)
-> IsString (Hash GenesisDelegateExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash GenesisDelegateExtendedKey
fromString :: String -> Hash GenesisDelegateExtendedKey
IsString) via UsingRawBytesHex (Hash GenesisDelegateExtendedKey)
  deriving (Typeable (Hash GenesisDelegateExtendedKey)
Typeable (Hash GenesisDelegateExtendedKey) =>
(Hash GenesisDelegateExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash GenesisDelegateExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash GenesisDelegateExtendedKey] -> Size)
-> ToCBOR (Hash GenesisDelegateExtendedKey)
Hash GenesisDelegateExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash GenesisDelegateExtendedKey -> Encoding
toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisDelegateExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisDelegateExtendedKey] -> Size
ToCBOR, Typeable (Hash GenesisDelegateExtendedKey)
Typeable (Hash GenesisDelegateExtendedKey) =>
(forall s. Decoder s (Hash GenesisDelegateExtendedKey))
-> (Proxy (Hash GenesisDelegateExtendedKey) -> Text)
-> FromCBOR (Hash GenesisDelegateExtendedKey)
Proxy (Hash GenesisDelegateExtendedKey) -> Text
forall s. Decoder s (Hash GenesisDelegateExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash GenesisDelegateExtendedKey)
fromCBOR :: forall s. Decoder s (Hash GenesisDelegateExtendedKey)
$clabel :: Proxy (Hash GenesisDelegateExtendedKey) -> Text
label :: Proxy (Hash GenesisDelegateExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash GenesisDelegateExtendedKey)
  deriving anyclass HasTypeProxy (Hash GenesisDelegateExtendedKey)
HasTypeProxy (Hash GenesisDelegateExtendedKey) =>
(Hash GenesisDelegateExtendedKey -> ByteString)
-> (AsType (Hash GenesisDelegateExtendedKey)
    -> ByteString
    -> Either DecoderError (Hash GenesisDelegateExtendedKey))
-> SerialiseAsCBOR (Hash GenesisDelegateExtendedKey)
AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey)
Hash GenesisDelegateExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash GenesisDelegateExtendedKey -> ByteString
serialiseToCBOR :: Hash GenesisDelegateExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey)
deserialiseFromCBOR :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either DecoderError (Hash GenesisDelegateExtendedKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) where
  serialiseToRawBytes :: Hash GenesisDelegateExtendedKey -> ByteString
serialiseToRawBytes (GenesisDelegateExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash GenesisDelegateExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (Hash GenesisDelegateExtendedKey)
deserialiseFromRawBytes (AsHash AsType GenesisDelegateExtendedKey
R:AsTypeGenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash GenesisDelegateExtendedKey)
-> Either
     SerialiseAsRawBytesError (Hash GenesisDelegateExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisDelegateExtendedKey: ") (Maybe (Hash GenesisDelegateExtendedKey)
 -> Either
      SerialiseAsRawBytesError (Hash GenesisDelegateExtendedKey))
-> Maybe (Hash GenesisDelegateExtendedKey)
-> Either
     SerialiseAsRawBytesError (Hash GenesisDelegateExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Staking -> Hash GenesisDelegateExtendedKey
GenesisDelegateExtendedKeyHash (KeyHash 'Staking -> Hash GenesisDelegateExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash GenesisDelegateExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Staking
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN)
 -> Hash GenesisDelegateExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash GenesisDelegateExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
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 -> VerificationKey GenesisDelegateKey
GenesisDelegateVerificationKey
      (VKey 'GenesisDelegate -> VerificationKey GenesisDelegateKey)
-> (XPub -> VKey 'GenesisDelegate)
-> XPub
-> VerificationKey GenesisDelegateKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'GenesisDelegate
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'GenesisDelegate)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'GenesisDelegate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey GenesisDelegateKey)
-> XPub -> VerificationKey GenesisDelegateKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey: byron and shelley key sizes do not match!"

--
-- Genesis UTxO keys
--

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)
    deriving stock VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
(VerificationKey GenesisUTxOKey
 -> VerificationKey GenesisUTxOKey -> Bool)
-> (VerificationKey GenesisUTxOKey
    -> VerificationKey GenesisUTxOKey -> Bool)
-> Eq (VerificationKey GenesisUTxOKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
== :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
$c/= :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
/= :: VerificationKey GenesisUTxOKey
-> VerificationKey GenesisUTxOKey -> Bool
Eq
    deriving (Int -> VerificationKey GenesisUTxOKey -> ShowS
[VerificationKey GenesisUTxOKey] -> ShowS
VerificationKey GenesisUTxOKey -> String
(Int -> VerificationKey GenesisUTxOKey -> ShowS)
-> (VerificationKey GenesisUTxOKey -> String)
-> ([VerificationKey GenesisUTxOKey] -> ShowS)
-> Show (VerificationKey GenesisUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS
showsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS
$cshow :: VerificationKey GenesisUTxOKey -> String
show :: VerificationKey GenesisUTxOKey -> String
$cshowList :: [VerificationKey GenesisUTxOKey] -> ShowS
showList :: [VerificationKey GenesisUTxOKey] -> ShowS
Show, String -> VerificationKey GenesisUTxOKey
(String -> VerificationKey GenesisUTxOKey)
-> IsString (VerificationKey GenesisUTxOKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey GenesisUTxOKey
fromString :: String -> VerificationKey GenesisUTxOKey
IsString) via UsingRawBytesHex (VerificationKey GenesisUTxOKey)
    deriving newtype (Typeable (VerificationKey GenesisUTxOKey)
Typeable (VerificationKey GenesisUTxOKey) =>
(VerificationKey GenesisUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey GenesisUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey GenesisUTxOKey] -> Size)
-> ToCBOR (VerificationKey GenesisUTxOKey)
VerificationKey GenesisUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VerificationKey GenesisUTxOKey -> Encoding
toCBOR :: VerificationKey GenesisUTxOKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey GenesisUTxOKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey GenesisUTxOKey] -> Size
ToCBOR, Typeable (VerificationKey GenesisUTxOKey)
Typeable (VerificationKey GenesisUTxOKey) =>
(forall s. Decoder s (VerificationKey GenesisUTxOKey))
-> (Proxy (VerificationKey GenesisUTxOKey) -> Text)
-> FromCBOR (VerificationKey GenesisUTxOKey)
Proxy (VerificationKey GenesisUTxOKey) -> Text
forall s. Decoder s (VerificationKey GenesisUTxOKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey GenesisUTxOKey)
fromCBOR :: forall s. Decoder s (VerificationKey GenesisUTxOKey)
$clabel :: Proxy (VerificationKey GenesisUTxOKey) -> Text
label :: Proxy (VerificationKey GenesisUTxOKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey GenesisUTxOKey)
HasTypeProxy (VerificationKey GenesisUTxOKey) =>
(VerificationKey GenesisUTxOKey -> ByteString)
-> (AsType (VerificationKey GenesisUTxOKey)
    -> ByteString
    -> Either DecoderError (VerificationKey GenesisUTxOKey))
-> SerialiseAsCBOR (VerificationKey GenesisUTxOKey)
AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey)
VerificationKey GenesisUTxOKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey GenesisUTxOKey -> ByteString
serialiseToCBOR :: VerificationKey GenesisUTxOKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey)
deserialiseFromCBOR :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either DecoderError (VerificationKey GenesisUTxOKey)
SerialiseAsCBOR

  newtype SigningKey GenesisUTxOKey
    = GenesisUTxOSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey GenesisUTxOKey -> ShowS
[SigningKey GenesisUTxOKey] -> ShowS
SigningKey GenesisUTxOKey -> String
(Int -> SigningKey GenesisUTxOKey -> ShowS)
-> (SigningKey GenesisUTxOKey -> String)
-> ([SigningKey GenesisUTxOKey] -> ShowS)
-> Show (SigningKey GenesisUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS
showsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS
$cshow :: SigningKey GenesisUTxOKey -> String
show :: SigningKey GenesisUTxOKey -> String
$cshowList :: [SigningKey GenesisUTxOKey] -> ShowS
showList :: [SigningKey GenesisUTxOKey] -> ShowS
Show, String -> SigningKey GenesisUTxOKey
(String -> SigningKey GenesisUTxOKey)
-> IsString (SigningKey GenesisUTxOKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey GenesisUTxOKey
fromString :: String -> SigningKey GenesisUTxOKey
IsString) via UsingRawBytesHex (SigningKey GenesisUTxOKey)
    deriving newtype (Typeable (SigningKey GenesisUTxOKey)
Typeable (SigningKey GenesisUTxOKey) =>
(SigningKey GenesisUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey GenesisUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey GenesisUTxOKey] -> Size)
-> ToCBOR (SigningKey GenesisUTxOKey)
SigningKey GenesisUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SigningKey GenesisUTxOKey -> Encoding
toCBOR :: SigningKey GenesisUTxOKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey GenesisUTxOKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey GenesisUTxOKey] -> Size
ToCBOR, Typeable (SigningKey GenesisUTxOKey)
Typeable (SigningKey GenesisUTxOKey) =>
(forall s. Decoder s (SigningKey GenesisUTxOKey))
-> (Proxy (SigningKey GenesisUTxOKey) -> Text)
-> FromCBOR (SigningKey GenesisUTxOKey)
Proxy (SigningKey GenesisUTxOKey) -> Text
forall s. Decoder s (SigningKey GenesisUTxOKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey GenesisUTxOKey)
fromCBOR :: forall s. Decoder s (SigningKey GenesisUTxOKey)
$clabel :: Proxy (SigningKey GenesisUTxOKey) -> Text
label :: Proxy (SigningKey GenesisUTxOKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey GenesisUTxOKey)
HasTypeProxy (SigningKey GenesisUTxOKey) =>
(SigningKey GenesisUTxOKey -> ByteString)
-> (AsType (SigningKey GenesisUTxOKey)
    -> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey))
-> SerialiseAsCBOR (SigningKey GenesisUTxOKey)
AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey)
SigningKey GenesisUTxOKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString
serialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey)
deserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey)
-> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType GenesisUTxOKey -> Crypto.Seed -> SigningKey GenesisUTxOKey
  deterministicSigningKey :: AsType GenesisUTxOKey -> Seed -> SigningKey GenesisUTxOKey
deterministicSigningKey AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey GenesisUTxOKey
GenesisUTxOSigningKey (Seed -> SignKeyDSIGN DSIGN
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 =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey
  getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey
getVerificationKey (GenesisUTxOSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'Payment -> VerificationKey GenesisUTxOKey
GenesisUTxOVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey
  verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey
verificationKeyHash (GenesisUTxOVerificationKey VKey 'Payment
vkey) =
    KeyHash 'Payment -> Hash GenesisUTxOKey
GenesisUTxOKeyHash (VKey 'Payment -> KeyHash 'Payment
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'Payment
vkey)

instance SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) where
  serialiseToRawBytes :: VerificationKey GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey GenesisUTxOKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey GenesisUTxOKey)
deserialiseFromRawBytes (AsVerificationKey AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey GenesisUTxOKey)
-> Either SerialiseAsRawBytesError (VerificationKey GenesisUTxOKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey GenesisUTxOKey") (Maybe (VerificationKey GenesisUTxOKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey GenesisUTxOKey))
-> Maybe (VerificationKey GenesisUTxOKey)
-> Either SerialiseAsRawBytesError (VerificationKey GenesisUTxOKey)
forall a b. (a -> b) -> a -> b
$
      VKey 'Payment -> VerificationKey GenesisUTxOKey
GenesisUTxOVerificationKey (VKey 'Payment -> VerificationKey GenesisUTxOKey)
-> (VerKeyDSIGN DSIGN -> VKey 'Payment)
-> VerKeyDSIGN DSIGN
-> VerificationKey GenesisUTxOKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (VerKeyDSIGN DSIGN -> VerificationKey GenesisUTxOKey)
-> Maybe (VerKeyDSIGN DSIGN)
-> Maybe (VerificationKey GenesisUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey GenesisUTxOKey) where
  serialiseToRawBytes :: SigningKey GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey GenesisUTxOKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey GenesisUTxOKey)
deserialiseFromRawBytes (AsSigningKey AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (SigningKey GenesisUTxOKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisUTxOKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey GenesisUTxOKey") (Maybe (SigningKey GenesisUTxOKey)
 -> Either SerialiseAsRawBytesError (SigningKey GenesisUTxOKey))
-> Maybe (SigningKey GenesisUTxOKey)
-> Either SerialiseAsRawBytesError (SigningKey GenesisUTxOKey)
forall a b. (a -> b) -> a -> b
$
      SignKeyDSIGN DSIGN -> SigningKey GenesisUTxOKey
GenesisUTxOSigningKey (SignKeyDSIGN DSIGN -> SigningKey GenesisUTxOKey)
-> Maybe (SignKeyDSIGN DSIGN) -> Maybe (SigningKey GenesisUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (SignKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs

newtype instance Hash GenesisUTxOKey
  = GenesisUTxOKeyHash {Hash GenesisUTxOKey -> KeyHash 'Payment
unGenesisUTxOKeyHash :: Shelley.KeyHash Shelley.Payment}
  deriving stock (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
(Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> Eq (Hash GenesisUTxOKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
== :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$c/= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
/= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
Eq, Eq (Hash GenesisUTxOKey)
Eq (Hash GenesisUTxOKey) =>
(Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool)
-> (Hash GenesisUTxOKey
    -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey)
-> (Hash GenesisUTxOKey
    -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey)
-> Ord (Hash GenesisUTxOKey)
Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering
Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering
compare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering
$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
>= :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool
$cmax :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
max :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
$cmin :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
min :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey
Ord)
  deriving (Int -> Hash GenesisUTxOKey -> ShowS
[Hash GenesisUTxOKey] -> ShowS
Hash GenesisUTxOKey -> String
(Int -> Hash GenesisUTxOKey -> ShowS)
-> (Hash GenesisUTxOKey -> String)
-> ([Hash GenesisUTxOKey] -> ShowS)
-> Show (Hash GenesisUTxOKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash GenesisUTxOKey -> ShowS
showsPrec :: Int -> Hash GenesisUTxOKey -> ShowS
$cshow :: Hash GenesisUTxOKey -> String
show :: Hash GenesisUTxOKey -> String
$cshowList :: [Hash GenesisUTxOKey] -> ShowS
showList :: [Hash GenesisUTxOKey] -> ShowS
Show, String -> Hash GenesisUTxOKey
(String -> Hash GenesisUTxOKey) -> IsString (Hash GenesisUTxOKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash GenesisUTxOKey
fromString :: String -> Hash GenesisUTxOKey
IsString) via UsingRawBytesHex (Hash GenesisUTxOKey)
  deriving (Typeable (Hash GenesisUTxOKey)
Typeable (Hash GenesisUTxOKey) =>
(Hash GenesisUTxOKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash GenesisUTxOKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash GenesisUTxOKey] -> Size)
-> ToCBOR (Hash GenesisUTxOKey)
Hash GenesisUTxOKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash GenesisUTxOKey -> Encoding
toCBOR :: Hash GenesisUTxOKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash GenesisUTxOKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash GenesisUTxOKey] -> Size
ToCBOR, Typeable (Hash GenesisUTxOKey)
Typeable (Hash GenesisUTxOKey) =>
(forall s. Decoder s (Hash GenesisUTxOKey))
-> (Proxy (Hash GenesisUTxOKey) -> Text)
-> FromCBOR (Hash GenesisUTxOKey)
Proxy (Hash GenesisUTxOKey) -> Text
forall s. Decoder s (Hash GenesisUTxOKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash GenesisUTxOKey)
fromCBOR :: forall s. Decoder s (Hash GenesisUTxOKey)
$clabel :: Proxy (Hash GenesisUTxOKey) -> Text
label :: Proxy (Hash GenesisUTxOKey) -> Text
FromCBOR) via UsingRawBytes (Hash GenesisUTxOKey)
  deriving anyclass HasTypeProxy (Hash GenesisUTxOKey)
HasTypeProxy (Hash GenesisUTxOKey) =>
(Hash GenesisUTxOKey -> ByteString)
-> (AsType (Hash GenesisUTxOKey)
    -> ByteString -> Either DecoderError (Hash GenesisUTxOKey))
-> SerialiseAsCBOR (Hash GenesisUTxOKey)
AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey)
Hash GenesisUTxOKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash GenesisUTxOKey -> ByteString
serialiseToCBOR :: Hash GenesisUTxOKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey)
deserialiseFromCBOR :: AsType (Hash GenesisUTxOKey)
-> ByteString -> Either DecoderError (Hash GenesisUTxOKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash GenesisUTxOKey) where
  serialiseToRawBytes :: Hash GenesisUTxOKey -> ByteString
serialiseToRawBytes (GenesisUTxOKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash GenesisUTxOKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash GenesisUTxOKey)
deserialiseFromRawBytes (AsHash AsType GenesisUTxOKey
R:AsTypeGenesisUTxOKey
AsGenesisUTxOKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash GenesisUTxOKey)
-> Either SerialiseAsRawBytesError (Hash GenesisUTxOKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash GenesisUTxOKey") (Maybe (Hash GenesisUTxOKey)
 -> Either SerialiseAsRawBytesError (Hash GenesisUTxOKey))
-> Maybe (Hash GenesisUTxOKey)
-> Either SerialiseAsRawBytesError (Hash GenesisUTxOKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'Payment -> Hash GenesisUTxOKey
GenesisUTxOKeyHash (KeyHash 'Payment -> Hash GenesisUTxOKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash GenesisUTxOKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash GenesisUTxOKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash GenesisUTxOKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey GenesisUTxOKey) where
  textEnvelopeType :: AsType (VerificationKey GenesisUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey GenesisUTxOKey)
_ =
    TextEnvelopeType
"GenesisUTxOVerificationKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey GenesisUTxOKey) where
  textEnvelopeType :: AsType (SigningKey GenesisUTxOKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey GenesisUTxOKey)
_ =
    TextEnvelopeType
"GenesisUTxOSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

-- TODO: use a different type from the stake pool key, since some operations
-- need a genesis key specifically

instance CastVerificationKeyRole GenesisUTxOKey PaymentKey where
  castVerificationKey :: VerificationKey GenesisUTxOKey -> VerificationKey PaymentKey
castVerificationKey (GenesisUTxOVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vkey)) =
    VKey 'Payment -> VerificationKey PaymentKey
PaymentVerificationKey (VerKeyDSIGN DSIGN -> VKey 'Payment
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey VerKeyDSIGN DSIGN
vkey)

instance CastSigningKeyRole GenesisUTxOKey PaymentKey where
  castSigningKey :: SigningKey GenesisUTxOKey -> SigningKey PaymentKey
castSigningKey (GenesisUTxOSigningKey SignKeyDSIGN DSIGN
skey) =
    SignKeyDSIGN DSIGN -> SigningKey PaymentKey
PaymentSigningKey SignKeyDSIGN DSIGN
skey

--
-- stake pool keys
--

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)
    deriving stock VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
(VerificationKey StakePoolKey
 -> VerificationKey StakePoolKey -> Bool)
-> (VerificationKey StakePoolKey
    -> VerificationKey StakePoolKey -> Bool)
-> Eq (VerificationKey StakePoolKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
== :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
$c/= :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
/= :: VerificationKey StakePoolKey
-> VerificationKey StakePoolKey -> Bool
Eq
    deriving (Int -> VerificationKey StakePoolKey -> ShowS
[VerificationKey StakePoolKey] -> ShowS
VerificationKey StakePoolKey -> String
(Int -> VerificationKey StakePoolKey -> ShowS)
-> (VerificationKey StakePoolKey -> String)
-> ([VerificationKey StakePoolKey] -> ShowS)
-> Show (VerificationKey StakePoolKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey StakePoolKey -> ShowS
showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS
$cshow :: VerificationKey StakePoolKey -> String
show :: VerificationKey StakePoolKey -> String
$cshowList :: [VerificationKey StakePoolKey] -> ShowS
showList :: [VerificationKey StakePoolKey] -> ShowS
Show, String -> VerificationKey StakePoolKey
(String -> VerificationKey StakePoolKey)
-> IsString (VerificationKey StakePoolKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey StakePoolKey
fromString :: String -> VerificationKey StakePoolKey
IsString) via UsingRawBytesHex (VerificationKey StakePoolKey)
    deriving newtype (Typeable (VerificationKey StakePoolKey)
Typeable (VerificationKey StakePoolKey) =>
(VerificationKey StakePoolKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey StakePoolKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey StakePoolKey] -> Size)
-> ToCBOR (VerificationKey StakePoolKey)
VerificationKey StakePoolKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: VerificationKey StakePoolKey -> Encoding
toCBOR :: VerificationKey StakePoolKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey StakePoolKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey StakePoolKey] -> Size
ToCBOR, Typeable (VerificationKey StakePoolKey)
Typeable (VerificationKey StakePoolKey) =>
(forall s. Decoder s (VerificationKey StakePoolKey))
-> (Proxy (VerificationKey StakePoolKey) -> Text)
-> FromCBOR (VerificationKey StakePoolKey)
Proxy (VerificationKey StakePoolKey) -> Text
forall s. Decoder s (VerificationKey StakePoolKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey StakePoolKey)
fromCBOR :: forall s. Decoder s (VerificationKey StakePoolKey)
$clabel :: Proxy (VerificationKey StakePoolKey) -> Text
label :: Proxy (VerificationKey StakePoolKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey StakePoolKey)
HasTypeProxy (VerificationKey StakePoolKey) =>
(VerificationKey StakePoolKey -> ByteString)
-> (AsType (VerificationKey StakePoolKey)
    -> ByteString
    -> Either DecoderError (VerificationKey StakePoolKey))
-> SerialiseAsCBOR (VerificationKey StakePoolKey)
AsType (VerificationKey StakePoolKey)
-> ByteString -> Either DecoderError (VerificationKey StakePoolKey)
VerificationKey StakePoolKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey StakePoolKey -> ByteString
serialiseToCBOR :: VerificationKey StakePoolKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey StakePoolKey)
-> ByteString -> Either DecoderError (VerificationKey StakePoolKey)
deserialiseFromCBOR :: AsType (VerificationKey StakePoolKey)
-> ByteString -> Either DecoderError (VerificationKey StakePoolKey)
SerialiseAsCBOR

  newtype SigningKey StakePoolKey
    = StakePoolSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey StakePoolKey -> ShowS
[SigningKey StakePoolKey] -> ShowS
SigningKey StakePoolKey -> String
(Int -> SigningKey StakePoolKey -> ShowS)
-> (SigningKey StakePoolKey -> String)
-> ([SigningKey StakePoolKey] -> ShowS)
-> Show (SigningKey StakePoolKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey StakePoolKey -> ShowS
showsPrec :: Int -> SigningKey StakePoolKey -> ShowS
$cshow :: SigningKey StakePoolKey -> String
show :: SigningKey StakePoolKey -> String
$cshowList :: [SigningKey StakePoolKey] -> ShowS
showList :: [SigningKey StakePoolKey] -> ShowS
Show, String -> SigningKey StakePoolKey
(String -> SigningKey StakePoolKey)
-> IsString (SigningKey StakePoolKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey StakePoolKey
fromString :: String -> SigningKey StakePoolKey
IsString) via UsingRawBytesHex (SigningKey StakePoolKey)
    deriving newtype (Typeable (SigningKey StakePoolKey)
Typeable (SigningKey StakePoolKey) =>
(SigningKey StakePoolKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey StakePoolKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey StakePoolKey] -> Size)
-> ToCBOR (SigningKey StakePoolKey)
SigningKey StakePoolKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: SigningKey StakePoolKey -> Encoding
toCBOR :: SigningKey StakePoolKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey StakePoolKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey StakePoolKey] -> Size
ToCBOR, Typeable (SigningKey StakePoolKey)
Typeable (SigningKey StakePoolKey) =>
(forall s. Decoder s (SigningKey StakePoolKey))
-> (Proxy (SigningKey StakePoolKey) -> Text)
-> FromCBOR (SigningKey StakePoolKey)
Proxy (SigningKey StakePoolKey) -> Text
forall s. Decoder s (SigningKey StakePoolKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey StakePoolKey)
fromCBOR :: forall s. Decoder s (SigningKey StakePoolKey)
$clabel :: Proxy (SigningKey StakePoolKey) -> Text
label :: Proxy (SigningKey StakePoolKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey StakePoolKey)
HasTypeProxy (SigningKey StakePoolKey) =>
(SigningKey StakePoolKey -> ByteString)
-> (AsType (SigningKey StakePoolKey)
    -> ByteString -> Either DecoderError (SigningKey StakePoolKey))
-> SerialiseAsCBOR (SigningKey StakePoolKey)
AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey)
SigningKey StakePoolKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey StakePoolKey -> ByteString
serialiseToCBOR :: SigningKey StakePoolKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey)
deserialiseFromCBOR :: AsType (SigningKey StakePoolKey)
-> ByteString -> Either DecoderError (SigningKey StakePoolKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType StakePoolKey -> Crypto.Seed -> SigningKey StakePoolKey
  deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey
deterministicSigningKey AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey StakePoolKey
StakePoolSigningKey (Seed -> SignKeyDSIGN DSIGN
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 =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey
  getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey
getVerificationKey (StakePoolSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'StakePool -> VerificationKey StakePoolKey
StakePoolVerificationKey (VerKeyDSIGN DSIGN -> VKey 'StakePool
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey
  verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey
verificationKeyHash (StakePoolVerificationKey VKey 'StakePool
vkey) =
    KeyHash 'StakePool -> Hash StakePoolKey
StakePoolKeyHash (VKey 'StakePool -> KeyHash 'StakePool
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'StakePool
vkey)

instance SerialiseAsRawBytes (VerificationKey StakePoolKey) where
  serialiseToRawBytes :: VerificationKey StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey StakePoolKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey StakePoolKey)
deserialiseFromRawBytes (AsVerificationKey AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey StakePoolKey)
-> Either SerialiseAsRawBytesError (VerificationKey StakePoolKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey StakePoolKey") (Maybe (VerificationKey StakePoolKey)
 -> Either SerialiseAsRawBytesError (VerificationKey StakePoolKey))
-> Maybe (VerificationKey StakePoolKey)
-> Either SerialiseAsRawBytesError (VerificationKey StakePoolKey)
forall a b. (a -> b) -> a -> b
$
      VKey 'StakePool -> VerificationKey StakePoolKey
StakePoolVerificationKey (VKey 'StakePool -> VerificationKey StakePoolKey)
-> (VerKeyDSIGN DSIGN -> VKey 'StakePool)
-> VerKeyDSIGN DSIGN
-> VerificationKey StakePoolKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'StakePool
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey StakePoolKey)
-> Maybe (VerKeyDSIGN DSIGN)
-> Maybe (VerificationKey StakePoolKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey StakePoolKey) where
  serialiseToRawBytes :: SigningKey StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey StakePoolKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
deserialiseFromRawBytes (AsSigningKey AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey) ByteString
bs =
    Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
-> (SignKeyDSIGN DSIGN
    -> Either SerialiseAsRawBytesError (SigningKey StakePoolKey))
-> Maybe (SignKeyDSIGN DSIGN)
-> Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      (SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey StakePoolKey"))
      (SigningKey StakePoolKey
-> Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
forall a b. b -> Either a b
Right (SigningKey StakePoolKey
 -> Either SerialiseAsRawBytesError (SigningKey StakePoolKey))
-> (SignKeyDSIGN DSIGN -> SigningKey StakePoolKey)
-> SignKeyDSIGN DSIGN
-> Either SerialiseAsRawBytesError (SigningKey StakePoolKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignKeyDSIGN DSIGN -> SigningKey StakePoolKey
StakePoolSigningKey)
      (ByteString -> Maybe (SignKeyDSIGN DSIGN)
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
unStakePoolKeyHash :: Shelley.KeyHash Shelley.StakePool}
  deriving stock (Hash StakePoolKey -> Hash StakePoolKey -> Bool
(Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> Eq (Hash StakePoolKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
== :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$c/= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
/= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
Eq, Eq (Hash StakePoolKey)
Eq (Hash StakePoolKey) =>
(Hash StakePoolKey -> Hash StakePoolKey -> Ordering)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Bool)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey)
-> (Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey)
-> Ord (Hash StakePoolKey)
Hash StakePoolKey -> Hash StakePoolKey -> Bool
Hash StakePoolKey -> Hash StakePoolKey -> Ordering
Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering
compare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering
$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
>= :: Hash StakePoolKey -> Hash StakePoolKey -> Bool
$cmax :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
max :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
$cmin :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
min :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey
Ord)
  deriving (Int -> Hash StakePoolKey -> ShowS
[Hash StakePoolKey] -> ShowS
Hash StakePoolKey -> String
(Int -> Hash StakePoolKey -> ShowS)
-> (Hash StakePoolKey -> String)
-> ([Hash StakePoolKey] -> ShowS)
-> Show (Hash StakePoolKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash StakePoolKey -> ShowS
showsPrec :: Int -> Hash StakePoolKey -> ShowS
$cshow :: Hash StakePoolKey -> String
show :: Hash StakePoolKey -> String
$cshowList :: [Hash StakePoolKey] -> ShowS
showList :: [Hash StakePoolKey] -> ShowS
Show, String -> Hash StakePoolKey
(String -> Hash StakePoolKey) -> IsString (Hash StakePoolKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash StakePoolKey
fromString :: String -> Hash StakePoolKey
IsString) via UsingRawBytesHex (Hash StakePoolKey)
  deriving (Typeable (Hash StakePoolKey)
Typeable (Hash StakePoolKey) =>
(Hash StakePoolKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash StakePoolKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash StakePoolKey] -> Size)
-> ToCBOR (Hash StakePoolKey)
Hash StakePoolKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: Hash StakePoolKey -> Encoding
toCBOR :: Hash StakePoolKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash StakePoolKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash StakePoolKey] -> Size
ToCBOR, Typeable (Hash StakePoolKey)
Typeable (Hash StakePoolKey) =>
(forall s. Decoder s (Hash StakePoolKey))
-> (Proxy (Hash StakePoolKey) -> Text)
-> FromCBOR (Hash StakePoolKey)
Proxy (Hash StakePoolKey) -> Text
forall s. Decoder s (Hash StakePoolKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash StakePoolKey)
fromCBOR :: forall s. Decoder s (Hash StakePoolKey)
$clabel :: Proxy (Hash StakePoolKey) -> Text
label :: Proxy (Hash StakePoolKey) -> Text
FromCBOR) via UsingRawBytes (Hash StakePoolKey)
  deriving anyclass HasTypeProxy (Hash StakePoolKey)
HasTypeProxy (Hash StakePoolKey) =>
(Hash StakePoolKey -> ByteString)
-> (AsType (Hash StakePoolKey)
    -> ByteString -> Either DecoderError (Hash StakePoolKey))
-> SerialiseAsCBOR (Hash StakePoolKey)
AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey)
Hash StakePoolKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash StakePoolKey -> ByteString
serialiseToCBOR :: Hash StakePoolKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey)
deserialiseFromCBOR :: AsType (Hash StakePoolKey)
-> ByteString -> Either DecoderError (Hash StakePoolKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash StakePoolKey) where
  serialiseToRawBytes :: Hash StakePoolKey -> ByteString
serialiseToRawBytes (StakePoolKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash StakePoolKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash StakePoolKey)
deserialiseFromRawBytes (AsHash AsType StakePoolKey
R:AsTypeStakePoolKey
AsStakePoolKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash StakePoolKey)
-> Either SerialiseAsRawBytesError (Hash StakePoolKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakePoolKey")
      (KeyHash 'StakePool -> Hash StakePoolKey
StakePoolKeyHash (KeyHash 'StakePool -> Hash StakePoolKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'StakePool)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash StakePoolKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'StakePool
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash StakePoolKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash StakePoolKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs)

instance SerialiseAsBech32 (Hash StakePoolKey) where
  bech32PrefixFor :: Hash StakePoolKey -> Text
bech32PrefixFor Hash StakePoolKey
_ = Text
"pool"
  bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text]
bech32PrefixesPermitted AsType (Hash StakePoolKey)
_ = [Text
"pool"]

instance ToJSON (Hash StakePoolKey) where
  toJSON :: Hash StakePoolKey -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (Hash StakePoolKey -> Text) -> Hash StakePoolKey -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash StakePoolKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32

instance ToJSONKey (Hash StakePoolKey) where
  toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey)
toJSONKey = (Hash StakePoolKey -> Text)
-> ToJSONKeyFunction (Hash StakePoolKey)
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText Hash StakePoolKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32

instance FromJSON (Hash StakePoolKey) where
  parseJSON :: Value -> Parser (Hash StakePoolKey)
parseJSON = String
-> (Text -> Parser (Hash StakePoolKey))
-> Value
-> Parser (Hash StakePoolKey)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"PoolId" ((Text -> Parser (Hash StakePoolKey))
 -> Value -> Parser (Hash StakePoolKey))
-> (Text -> Parser (Hash StakePoolKey))
-> Value
-> Parser (Hash StakePoolKey)
forall a b. (a -> b) -> a -> b
$ \Text
str ->
    case AsType (Hash StakePoolKey)
-> Text -> Either Bech32DecodeError (Hash StakePoolKey)
forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 (AsType StakePoolKey -> AsType (Hash StakePoolKey)
forall a. AsType a -> AsType (Hash a)
AsHash AsType StakePoolKey
AsStakePoolKey) Text
str of
      Left Bech32DecodeError
err ->
        String -> Parser (Hash StakePoolKey)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (Hash StakePoolKey))
-> String -> Parser (Hash StakePoolKey)
forall a b. (a -> b) -> a -> b
$
          Doc AnsiStyle -> String
docToString (Doc AnsiStyle -> String) -> Doc AnsiStyle -> String
forall a b. (a -> b) -> a -> b
$
            [Doc AnsiStyle] -> Doc AnsiStyle
forall a. Monoid a => [a] -> a
mconcat
              [ Doc AnsiStyle
"Error deserialising Hash StakePoolKey: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Text
str
              , Doc AnsiStyle
" Error: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Bech32DecodeError -> Doc AnsiStyle
forall e ann. Error e => e -> Doc ann
forall ann. Bech32DecodeError -> Doc ann
prettyError Bech32DecodeError
err
              ]
      Right Hash StakePoolKey
h -> Hash StakePoolKey -> Parser (Hash StakePoolKey)
forall a. a -> Parser a
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_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey StakePoolKey) where
  textEnvelopeType :: AsType (SigningKey StakePoolKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakePoolKey)
_ =
    TextEnvelopeType
"StakePoolSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

---
--- Stake pool extended keys
---

data StakePoolExtendedKey

instance HasTypeProxy StakePoolExtendedKey where
  data AsType StakePoolExtendedKey = AsStakePoolExtendedKey
  proxyToAsType :: Proxy StakePoolExtendedKey -> AsType StakePoolExtendedKey
proxyToAsType Proxy StakePoolExtendedKey
_ = AsType StakePoolExtendedKey
AsStakePoolExtendedKey

instance Key StakePoolExtendedKey where
  newtype VerificationKey StakePoolExtendedKey
    = StakePoolExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey StakePoolExtendedKey
-> VerificationKey StakePoolExtendedKey -> Bool
(VerificationKey StakePoolExtendedKey
 -> VerificationKey StakePoolExtendedKey -> Bool)
-> (VerificationKey StakePoolExtendedKey
    -> VerificationKey StakePoolExtendedKey -> Bool)
-> Eq (VerificationKey StakePoolExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey StakePoolExtendedKey
-> VerificationKey StakePoolExtendedKey -> Bool
== :: VerificationKey StakePoolExtendedKey
-> VerificationKey StakePoolExtendedKey -> Bool
$c/= :: VerificationKey StakePoolExtendedKey
-> VerificationKey StakePoolExtendedKey -> Bool
/= :: VerificationKey StakePoolExtendedKey
-> VerificationKey StakePoolExtendedKey -> Bool
Eq
    deriving (Int -> VerificationKey StakePoolExtendedKey -> ShowS
[VerificationKey StakePoolExtendedKey] -> ShowS
VerificationKey StakePoolExtendedKey -> String
(Int -> VerificationKey StakePoolExtendedKey -> ShowS)
-> (VerificationKey StakePoolExtendedKey -> String)
-> ([VerificationKey StakePoolExtendedKey] -> ShowS)
-> Show (VerificationKey StakePoolExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey StakePoolExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey StakePoolExtendedKey -> ShowS
$cshow :: VerificationKey StakePoolExtendedKey -> String
show :: VerificationKey StakePoolExtendedKey -> String
$cshowList :: [VerificationKey StakePoolExtendedKey] -> ShowS
showList :: [VerificationKey StakePoolExtendedKey] -> ShowS
Show, String -> VerificationKey StakePoolExtendedKey
(String -> VerificationKey StakePoolExtendedKey)
-> IsString (VerificationKey StakePoolExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey StakePoolExtendedKey
fromString :: String -> VerificationKey StakePoolExtendedKey
IsString) via UsingRawBytesHex (VerificationKey StakePoolExtendedKey)
    deriving anyclass HasTypeProxy (VerificationKey StakePoolExtendedKey)
HasTypeProxy (VerificationKey StakePoolExtendedKey) =>
(VerificationKey StakePoolExtendedKey -> ByteString)
-> (AsType (VerificationKey StakePoolExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey StakePoolExtendedKey))
-> SerialiseAsCBOR (VerificationKey StakePoolExtendedKey)
AsType (VerificationKey StakePoolExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakePoolExtendedKey)
VerificationKey StakePoolExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey StakePoolExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey StakePoolExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey StakePoolExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakePoolExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey StakePoolExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey StakePoolExtendedKey)
SerialiseAsCBOR

  newtype SigningKey StakePoolExtendedKey
    = StakePoolExtendedSigningKey Crypto.HD.XPrv
    deriving (Int -> SigningKey StakePoolExtendedKey -> ShowS
[SigningKey StakePoolExtendedKey] -> ShowS
SigningKey StakePoolExtendedKey -> String
(Int -> SigningKey StakePoolExtendedKey -> ShowS)
-> (SigningKey StakePoolExtendedKey -> String)
-> ([SigningKey StakePoolExtendedKey] -> ShowS)
-> Show (SigningKey StakePoolExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey StakePoolExtendedKey -> ShowS
showsPrec :: Int -> SigningKey StakePoolExtendedKey -> ShowS
$cshow :: SigningKey StakePoolExtendedKey -> String
show :: SigningKey StakePoolExtendedKey -> String
$cshowList :: [SigningKey StakePoolExtendedKey] -> ShowS
showList :: [SigningKey StakePoolExtendedKey] -> ShowS
Show, String -> SigningKey StakePoolExtendedKey
(String -> SigningKey StakePoolExtendedKey)
-> IsString (SigningKey StakePoolExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey StakePoolExtendedKey
fromString :: String -> SigningKey StakePoolExtendedKey
IsString) via UsingRawBytesHex (SigningKey StakePoolExtendedKey)
    deriving anyclass HasTypeProxy (SigningKey StakePoolExtendedKey)
HasTypeProxy (SigningKey StakePoolExtendedKey) =>
(SigningKey StakePoolExtendedKey -> ByteString)
-> (AsType (SigningKey StakePoolExtendedKey)
    -> ByteString
    -> Either DecoderError (SigningKey StakePoolExtendedKey))
-> SerialiseAsCBOR (SigningKey StakePoolExtendedKey)
AsType (SigningKey StakePoolExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey StakePoolExtendedKey)
SigningKey StakePoolExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey StakePoolExtendedKey -> ByteString
serialiseToCBOR :: SigningKey StakePoolExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey StakePoolExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey StakePoolExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey StakePoolExtendedKey)
-> ByteString
-> Either DecoderError (SigningKey StakePoolExtendedKey)
SerialiseAsCBOR

  deterministicSigningKey
    :: AsType StakePoolExtendedKey
    -> Crypto.Seed
    -> SigningKey StakePoolExtendedKey
  deterministicSigningKey :: AsType StakePoolExtendedKey
-> Seed -> SigningKey StakePoolExtendedKey
deterministicSigningKey AsType StakePoolExtendedKey
R:AsTypeStakePoolExtendedKey
AsStakePoolExtendedKey Seed
seed =
    XPrv -> SigningKey StakePoolExtendedKey
StakePoolExtendedSigningKey
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType StakePoolExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType StakePoolExtendedKey -> Word
deterministicSigningKeySeedSize AsType StakePoolExtendedKey
R:AsTypeStakePoolExtendedKey
AsStakePoolExtendedKey = Word
32

  getVerificationKey
    :: SigningKey StakePoolExtendedKey
    -> VerificationKey StakePoolExtendedKey
  getVerificationKey :: SigningKey StakePoolExtendedKey
-> VerificationKey StakePoolExtendedKey
getVerificationKey (StakePoolExtendedSigningKey XPrv
sk) =
    XPub -> VerificationKey StakePoolExtendedKey
StakePoolExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey StakePoolExtendedKey
    -> Hash StakePoolExtendedKey
  verificationKeyHash :: VerificationKey StakePoolExtendedKey -> Hash StakePoolExtendedKey
verificationKeyHash (StakePoolExtendedVerificationKey XPub
vk) =
    KeyHash 'StakePool -> Hash StakePoolExtendedKey
StakePoolExtendedKeyHash
      (KeyHash 'StakePool -> Hash StakePoolExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'StakePool)
-> Hash ADDRHASH XPub
-> Hash StakePoolExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'StakePool
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'StakePool)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'StakePool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash StakePoolExtendedKey)
-> Hash ADDRHASH XPub -> Hash StakePoolExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

instance ToCBOR (VerificationKey StakePoolExtendedKey) where
  toCBOR :: VerificationKey StakePoolExtendedKey -> Encoding
toCBOR (StakePoolExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)

instance FromCBOR (VerificationKey StakePoolExtendedKey) where
  fromCBOR :: forall s. Decoder s (VerificationKey StakePoolExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey StakePoolExtendedKey))
-> (XPub -> Decoder s (VerificationKey StakePoolExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey StakePoolExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey StakePoolExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey StakePoolExtendedKey
-> Decoder s (VerificationKey StakePoolExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey StakePoolExtendedKey
 -> Decoder s (VerificationKey StakePoolExtendedKey))
-> (XPub -> VerificationKey StakePoolExtendedKey)
-> XPub
-> Decoder s (VerificationKey StakePoolExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey StakePoolExtendedKey
StakePoolExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey StakePoolExtendedKey) where
  toCBOR :: SigningKey StakePoolExtendedKey -> Encoding
toCBOR (StakePoolExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)

instance FromCBOR (SigningKey StakePoolExtendedKey) where
  fromCBOR :: forall s. Decoder s (SigningKey StakePoolExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey StakePoolExtendedKey))
-> (XPrv -> Decoder s (SigningKey StakePoolExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey StakePoolExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey StakePoolExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey StakePoolExtendedKey
-> Decoder s (SigningKey StakePoolExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey StakePoolExtendedKey
 -> Decoder s (SigningKey StakePoolExtendedKey))
-> (XPrv -> SigningKey StakePoolExtendedKey)
-> XPrv
-> Decoder s (SigningKey StakePoolExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey StakePoolExtendedKey
StakePoolExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey StakePoolExtendedKey) where
  serialiseToRawBytes :: VerificationKey StakePoolExtendedKey -> ByteString
serialiseToRawBytes (StakePoolExtendedVerificationKey XPub
xpub) =
    XPub -> ByteString
Crypto.HD.unXPub XPub
xpub

  deserialiseFromRawBytes :: AsType (VerificationKey StakePoolExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey StakePoolExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType StakePoolExtendedKey
R:AsTypeStakePoolExtendedKey
AsStakePoolExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey StakePoolExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey StakePoolExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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 StakePoolExtendedKey: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg)
      )
      (Either String (VerificationKey StakePoolExtendedKey)
 -> Either
      SerialiseAsRawBytesError (VerificationKey StakePoolExtendedKey))
-> Either String (VerificationKey StakePoolExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey StakePoolExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPub -> VerificationKey StakePoolExtendedKey
StakePoolExtendedVerificationKey (XPub -> VerificationKey StakePoolExtendedKey)
-> Either String XPub
-> Either String (VerificationKey StakePoolExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs

instance SerialiseAsRawBytes (SigningKey StakePoolExtendedKey) where
  serialiseToRawBytes :: SigningKey StakePoolExtendedKey -> ByteString
serialiseToRawBytes (StakePoolExtendedSigningKey XPrv
xprv) =
    XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv

  deserialiseFromRawBytes :: AsType (SigningKey StakePoolExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (SigningKey StakePoolExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType StakePoolExtendedKey
R:AsTypeStakePoolExtendedKey
AsStakePoolExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey StakePoolExtendedKey)
-> Either
     SerialiseAsRawBytesError (SigningKey StakePoolExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
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 StakePoolExtendedKey: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg)
      )
      (Either String (SigningKey StakePoolExtendedKey)
 -> Either
      SerialiseAsRawBytesError (SigningKey StakePoolExtendedKey))
-> Either String (SigningKey StakePoolExtendedKey)
-> Either
     SerialiseAsRawBytesError (SigningKey StakePoolExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPrv -> SigningKey StakePoolExtendedKey
StakePoolExtendedSigningKey (XPrv -> SigningKey StakePoolExtendedKey)
-> Either String XPrv
-> Either String (SigningKey StakePoolExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs

newtype instance Hash StakePoolExtendedKey
  = StakePoolExtendedKeyHash
  {Hash StakePoolExtendedKey -> KeyHash 'StakePool
unStakePoolExtendedKeyHash :: Shelley.KeyHash Shelley.StakePool}
  deriving stock (Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
(Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool)
-> (Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool)
-> Eq (Hash StakePoolExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
== :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
$c/= :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
/= :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
Eq, Eq (Hash StakePoolExtendedKey)
Eq (Hash StakePoolExtendedKey) =>
(Hash StakePoolExtendedKey
 -> Hash StakePoolExtendedKey -> Ordering)
-> (Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool)
-> (Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool)
-> (Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool)
-> (Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool)
-> (Hash StakePoolExtendedKey
    -> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey)
-> (Hash StakePoolExtendedKey
    -> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey)
-> Ord (Hash StakePoolExtendedKey)
Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Ordering
Hash StakePoolExtendedKey
-> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey
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
$ccompare :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Ordering
compare :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Ordering
$c< :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
< :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
$c<= :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
<= :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
$c> :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
> :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
$c>= :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
>= :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool
$cmax :: Hash StakePoolExtendedKey
-> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey
max :: Hash StakePoolExtendedKey
-> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey
$cmin :: Hash StakePoolExtendedKey
-> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey
min :: Hash StakePoolExtendedKey
-> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey
Ord, Int -> Hash StakePoolExtendedKey -> ShowS
[Hash StakePoolExtendedKey] -> ShowS
Hash StakePoolExtendedKey -> String
(Int -> Hash StakePoolExtendedKey -> ShowS)
-> (Hash StakePoolExtendedKey -> String)
-> ([Hash StakePoolExtendedKey] -> ShowS)
-> Show (Hash StakePoolExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash StakePoolExtendedKey -> ShowS
showsPrec :: Int -> Hash StakePoolExtendedKey -> ShowS
$cshow :: Hash StakePoolExtendedKey -> String
show :: Hash StakePoolExtendedKey -> String
$cshowList :: [Hash StakePoolExtendedKey] -> ShowS
showList :: [Hash StakePoolExtendedKey] -> ShowS
Show)

instance SerialiseAsRawBytes (Hash StakePoolExtendedKey) where
  serialiseToRawBytes :: Hash StakePoolExtendedKey -> ByteString
serialiseToRawBytes (StakePoolExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash StakePoolExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash StakePoolExtendedKey)
deserialiseFromRawBytes (AsHash AsType StakePoolExtendedKey
R:AsTypeStakePoolExtendedKey
AsStakePoolExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash StakePoolExtendedKey)
-> Either SerialiseAsRawBytesError (Hash StakePoolExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash StakePoolExtendedKey")
      (KeyHash 'StakePool -> Hash StakePoolExtendedKey
StakePoolExtendedKeyHash (KeyHash 'StakePool -> Hash StakePoolExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'StakePool)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash StakePoolExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'StakePool
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash StakePoolExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash StakePoolExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs)

instance HasTextEnvelope (VerificationKey StakePoolExtendedKey) where
  textEnvelopeType :: AsType (VerificationKey StakePoolExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey StakePoolExtendedKey)
_ = TextEnvelopeType
"StakePoolExtendedVerificationKey_ed25519_bip32"

instance HasTextEnvelope (SigningKey StakePoolExtendedKey) where
  textEnvelopeType :: AsType (SigningKey StakePoolExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey StakePoolExtendedKey)
_ = TextEnvelopeType
"StakePoolExtendedSigningKey_ed25519_bip32"

instance SerialiseAsBech32 (VerificationKey StakePoolExtendedKey) where
  bech32PrefixFor :: VerificationKey StakePoolExtendedKey -> Text
bech32PrefixFor VerificationKey StakePoolExtendedKey
_ = Text
"pool_xvk"
  bech32PrefixesPermitted :: AsType (VerificationKey StakePoolExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey StakePoolExtendedKey)
_ = [Text
"pool_xvk"]

instance SerialiseAsBech32 (SigningKey StakePoolExtendedKey) where
  bech32PrefixFor :: SigningKey StakePoolExtendedKey -> Text
bech32PrefixFor SigningKey StakePoolExtendedKey
_ = Text
"pool_xsk"
  bech32PrefixesPermitted :: AsType (SigningKey StakePoolExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey StakePoolExtendedKey)
_ = [Text
"pool_xsk"]

instance CastVerificationKeyRole StakePoolExtendedKey StakePoolKey where
  castVerificationKey :: VerificationKey StakePoolExtendedKey
-> VerificationKey StakePoolKey
castVerificationKey (StakePoolExtendedVerificationKey XPub
vk) =
    VKey 'StakePool -> VerificationKey StakePoolKey
StakePoolVerificationKey
      (VKey 'StakePool -> VerificationKey StakePoolKey)
-> (XPub -> VKey 'StakePool)
-> XPub
-> VerificationKey StakePoolKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'StakePool
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'StakePool)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'StakePool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey StakePoolKey)
-> XPub -> VerificationKey StakePoolKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey (StakePoolKey): byron and shelley key sizes do not match!"

--
-- DRep keys
--

data DRepKey

instance HasTypeProxy DRepKey where
  data AsType DRepKey = AsDRepKey
  proxyToAsType :: Proxy DRepKey -> AsType DRepKey
proxyToAsType Proxy DRepKey
_ = AsType DRepKey
AsDRepKey

instance Key DRepKey where
  newtype VerificationKey DRepKey
    = DRepVerificationKey (Shelley.VKey Shelley.DRepRole)
    deriving stock VerificationKey DRepKey -> VerificationKey DRepKey -> Bool
(VerificationKey DRepKey -> VerificationKey DRepKey -> Bool)
-> (VerificationKey DRepKey -> VerificationKey DRepKey -> Bool)
-> Eq (VerificationKey DRepKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool
== :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool
$c/= :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool
/= :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool
Eq
    deriving (Int -> VerificationKey DRepKey -> ShowS
[VerificationKey DRepKey] -> ShowS
VerificationKey DRepKey -> String
(Int -> VerificationKey DRepKey -> ShowS)
-> (VerificationKey DRepKey -> String)
-> ([VerificationKey DRepKey] -> ShowS)
-> Show (VerificationKey DRepKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey DRepKey -> ShowS
showsPrec :: Int -> VerificationKey DRepKey -> ShowS
$cshow :: VerificationKey DRepKey -> String
show :: VerificationKey DRepKey -> String
$cshowList :: [VerificationKey DRepKey] -> ShowS
showList :: [VerificationKey DRepKey] -> ShowS
Show, String -> VerificationKey DRepKey
(String -> VerificationKey DRepKey)
-> IsString (VerificationKey DRepKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey DRepKey
fromString :: String -> VerificationKey DRepKey
IsString) via UsingRawBytesHex (VerificationKey DRepKey)
    deriving newtype (Typeable (VerificationKey DRepKey)
Typeable (VerificationKey DRepKey) =>
(VerificationKey DRepKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (VerificationKey DRepKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [VerificationKey DRepKey] -> Size)
-> ToCBOR (VerificationKey DRepKey)
VerificationKey DRepKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey DRepKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey DRepKey) -> 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
$ctoCBOR :: VerificationKey DRepKey -> Encoding
toCBOR :: VerificationKey DRepKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey DRepKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey DRepKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey DRepKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey DRepKey] -> Size
ToCBOR, Typeable (VerificationKey DRepKey)
Typeable (VerificationKey DRepKey) =>
(forall s. Decoder s (VerificationKey DRepKey))
-> (Proxy (VerificationKey DRepKey) -> Text)
-> FromCBOR (VerificationKey DRepKey)
Proxy (VerificationKey DRepKey) -> Text
forall s. Decoder s (VerificationKey DRepKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (VerificationKey DRepKey)
fromCBOR :: forall s. Decoder s (VerificationKey DRepKey)
$clabel :: Proxy (VerificationKey DRepKey) -> Text
label :: Proxy (VerificationKey DRepKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (VerificationKey DRepKey)
HasTypeProxy (VerificationKey DRepKey) =>
(VerificationKey DRepKey -> ByteString)
-> (AsType (VerificationKey DRepKey)
    -> ByteString -> Either DecoderError (VerificationKey DRepKey))
-> SerialiseAsCBOR (VerificationKey DRepKey)
AsType (VerificationKey DRepKey)
-> ByteString -> Either DecoderError (VerificationKey DRepKey)
VerificationKey DRepKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey DRepKey -> ByteString
serialiseToCBOR :: VerificationKey DRepKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey DRepKey)
-> ByteString -> Either DecoderError (VerificationKey DRepKey)
deserialiseFromCBOR :: AsType (VerificationKey DRepKey)
-> ByteString -> Either DecoderError (VerificationKey DRepKey)
SerialiseAsCBOR

  newtype SigningKey DRepKey
    = DRepSigningKey (DSIGN.SignKeyDSIGN DSIGN)
    deriving (Int -> SigningKey DRepKey -> ShowS
[SigningKey DRepKey] -> ShowS
SigningKey DRepKey -> String
(Int -> SigningKey DRepKey -> ShowS)
-> (SigningKey DRepKey -> String)
-> ([SigningKey DRepKey] -> ShowS)
-> Show (SigningKey DRepKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey DRepKey -> ShowS
showsPrec :: Int -> SigningKey DRepKey -> ShowS
$cshow :: SigningKey DRepKey -> String
show :: SigningKey DRepKey -> String
$cshowList :: [SigningKey DRepKey] -> ShowS
showList :: [SigningKey DRepKey] -> ShowS
Show, String -> SigningKey DRepKey
(String -> SigningKey DRepKey) -> IsString (SigningKey DRepKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey DRepKey
fromString :: String -> SigningKey DRepKey
IsString) via UsingRawBytesHex (SigningKey DRepKey)
    deriving newtype (Typeable (SigningKey DRepKey)
Typeable (SigningKey DRepKey) =>
(SigningKey DRepKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (SigningKey DRepKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [SigningKey DRepKey] -> Size)
-> ToCBOR (SigningKey DRepKey)
SigningKey DRepKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey DRepKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey DRepKey) -> 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
$ctoCBOR :: SigningKey DRepKey -> Encoding
toCBOR :: SigningKey DRepKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey DRepKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey DRepKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey DRepKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey DRepKey] -> Size
ToCBOR, Typeable (SigningKey DRepKey)
Typeable (SigningKey DRepKey) =>
(forall s. Decoder s (SigningKey DRepKey))
-> (Proxy (SigningKey DRepKey) -> Text)
-> FromCBOR (SigningKey DRepKey)
Proxy (SigningKey DRepKey) -> Text
forall s. Decoder s (SigningKey DRepKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (SigningKey DRepKey)
fromCBOR :: forall s. Decoder s (SigningKey DRepKey)
$clabel :: Proxy (SigningKey DRepKey) -> Text
label :: Proxy (SigningKey DRepKey) -> Text
FromCBOR)
    deriving anyclass HasTypeProxy (SigningKey DRepKey)
HasTypeProxy (SigningKey DRepKey) =>
(SigningKey DRepKey -> ByteString)
-> (AsType (SigningKey DRepKey)
    -> ByteString -> Either DecoderError (SigningKey DRepKey))
-> SerialiseAsCBOR (SigningKey DRepKey)
AsType (SigningKey DRepKey)
-> ByteString -> Either DecoderError (SigningKey DRepKey)
SigningKey DRepKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey DRepKey -> ByteString
serialiseToCBOR :: SigningKey DRepKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey DRepKey)
-> ByteString -> Either DecoderError (SigningKey DRepKey)
deserialiseFromCBOR :: AsType (SigningKey DRepKey)
-> ByteString -> Either DecoderError (SigningKey DRepKey)
SerialiseAsCBOR

  deterministicSigningKey :: AsType DRepKey -> Crypto.Seed -> SigningKey DRepKey
  deterministicSigningKey :: AsType DRepKey -> Seed -> SigningKey DRepKey
deterministicSigningKey AsType DRepKey
R:AsTypeDRepKey
AsDRepKey Seed
seed =
    SignKeyDSIGN DSIGN -> SigningKey DRepKey
DRepSigningKey (Seed -> SignKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
Crypto.genKeyDSIGN Seed
seed)

  deterministicSigningKeySeedSize :: AsType DRepKey -> Word
  deterministicSigningKeySeedSize :: AsType DRepKey -> Word
deterministicSigningKeySeedSize AsType DRepKey
R:AsTypeDRepKey
AsDRepKey =
    Proxy DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
Crypto.seedSizeDSIGN Proxy DSIGN
proxy
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

  getVerificationKey :: SigningKey DRepKey -> VerificationKey DRepKey
  getVerificationKey :: SigningKey DRepKey -> VerificationKey DRepKey
getVerificationKey (DRepSigningKey SignKeyDSIGN DSIGN
sk) =
    VKey 'DRepRole -> VerificationKey DRepKey
DRepVerificationKey (VerKeyDSIGN DSIGN -> VKey 'DRepRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey (SignKeyDSIGN DSIGN -> VerKeyDSIGN DSIGN
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
Crypto.deriveVerKeyDSIGN SignKeyDSIGN DSIGN
sk))

  verificationKeyHash :: VerificationKey DRepKey -> Hash DRepKey
  verificationKeyHash :: VerificationKey DRepKey -> Hash DRepKey
verificationKeyHash (DRepVerificationKey VKey 'DRepRole
vkey) =
    KeyHash 'DRepRole -> Hash DRepKey
DRepKeyHash (VKey 'DRepRole -> KeyHash 'DRepRole
forall (kd :: KeyRole). VKey kd -> KeyHash kd
Shelley.hashKey VKey 'DRepRole
vkey)

instance SerialiseAsRawBytes (VerificationKey DRepKey) where
  serialiseToRawBytes :: VerificationKey DRepKey -> ByteString
serialiseToRawBytes (DRepVerificationKey (Shelley.VKey VerKeyDSIGN DSIGN
vk)) =
    VerKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
Crypto.rawSerialiseVerKeyDSIGN VerKeyDSIGN DSIGN
vk

  deserialiseFromRawBytes :: AsType (VerificationKey DRepKey)
-> ByteString
-> Either SerialiseAsRawBytesError (VerificationKey DRepKey)
deserialiseFromRawBytes (AsVerificationKey AsType DRepKey
R:AsTypeDRepKey
AsDRepKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (VerificationKey DRepKey)
-> Either SerialiseAsRawBytesError (VerificationKey DRepKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey DRepKey") (Maybe (VerificationKey DRepKey)
 -> Either SerialiseAsRawBytesError (VerificationKey DRepKey))
-> Maybe (VerificationKey DRepKey)
-> Either SerialiseAsRawBytesError (VerificationKey DRepKey)
forall a b. (a -> b) -> a -> b
$
      VKey 'DRepRole -> VerificationKey DRepKey
DRepVerificationKey (VKey 'DRepRole -> VerificationKey DRepKey)
-> (VerKeyDSIGN DSIGN -> VKey 'DRepRole)
-> VerKeyDSIGN DSIGN
-> VerificationKey DRepKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'DRepRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
        (VerKeyDSIGN DSIGN -> VerificationKey DRepKey)
-> Maybe (VerKeyDSIGN DSIGN) -> Maybe (VerificationKey DRepKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN ByteString
bs

instance SerialiseAsRawBytes (SigningKey DRepKey) where
  serialiseToRawBytes :: SigningKey DRepKey -> ByteString
serialiseToRawBytes (DRepSigningKey SignKeyDSIGN DSIGN
sk) =
    SignKeyDSIGN DSIGN -> ByteString
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
Crypto.rawSerialiseSignKeyDSIGN SignKeyDSIGN DSIGN
sk

  deserialiseFromRawBytes :: AsType (SigningKey DRepKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey DRepKey)
deserialiseFromRawBytes (AsSigningKey AsType DRepKey
R:AsTypeDRepKey
AsDRepKey) ByteString
bs =
    Either SerialiseAsRawBytesError (SigningKey DRepKey)
-> (SignKeyDSIGN DSIGN
    -> Either SerialiseAsRawBytesError (SigningKey DRepKey))
-> Maybe (SignKeyDSIGN DSIGN)
-> Either SerialiseAsRawBytesError (SigningKey DRepKey)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      (SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (SigningKey DRepKey)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey DRepKey"))
      (SigningKey DRepKey
-> Either SerialiseAsRawBytesError (SigningKey DRepKey)
forall a b. b -> Either a b
Right (SigningKey DRepKey
 -> Either SerialiseAsRawBytesError (SigningKey DRepKey))
-> (SignKeyDSIGN DSIGN -> SigningKey DRepKey)
-> SignKeyDSIGN DSIGN
-> Either SerialiseAsRawBytesError (SigningKey DRepKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignKeyDSIGN DSIGN -> SigningKey DRepKey
DRepSigningKey)
      (ByteString -> Maybe (SignKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
Crypto.rawDeserialiseSignKeyDSIGN ByteString
bs)

instance SerialiseAsBech32 (VerificationKey DRepKey) where
  bech32PrefixFor :: VerificationKey DRepKey -> Text
bech32PrefixFor VerificationKey DRepKey
_ = Text
"drep_vk"
  bech32PrefixesPermitted :: AsType (VerificationKey DRepKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey DRepKey)
_ = [Text
"drep_vk"]

instance SerialiseAsBech32 (SigningKey DRepKey) where
  bech32PrefixFor :: SigningKey DRepKey -> Text
bech32PrefixFor SigningKey DRepKey
_ = Text
"drep_sk"
  bech32PrefixesPermitted :: AsType (SigningKey DRepKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey DRepKey)
_ = [Text
"drep_sk"]

newtype instance Hash DRepKey
  = DRepKeyHash {Hash DRepKey -> KeyHash 'DRepRole
unDRepKeyHash :: Shelley.KeyHash Shelley.DRepRole}
  deriving stock (Hash DRepKey -> Hash DRepKey -> Bool
(Hash DRepKey -> Hash DRepKey -> Bool)
-> (Hash DRepKey -> Hash DRepKey -> Bool) -> Eq (Hash DRepKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash DRepKey -> Hash DRepKey -> Bool
== :: Hash DRepKey -> Hash DRepKey -> Bool
$c/= :: Hash DRepKey -> Hash DRepKey -> Bool
/= :: Hash DRepKey -> Hash DRepKey -> Bool
Eq, Eq (Hash DRepKey)
Eq (Hash DRepKey) =>
(Hash DRepKey -> Hash DRepKey -> Ordering)
-> (Hash DRepKey -> Hash DRepKey -> Bool)
-> (Hash DRepKey -> Hash DRepKey -> Bool)
-> (Hash DRepKey -> Hash DRepKey -> Bool)
-> (Hash DRepKey -> Hash DRepKey -> Bool)
-> (Hash DRepKey -> Hash DRepKey -> Hash DRepKey)
-> (Hash DRepKey -> Hash DRepKey -> Hash DRepKey)
-> Ord (Hash DRepKey)
Hash DRepKey -> Hash DRepKey -> Bool
Hash DRepKey -> Hash DRepKey -> Ordering
Hash DRepKey -> Hash DRepKey -> Hash DRepKey
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
$ccompare :: Hash DRepKey -> Hash DRepKey -> Ordering
compare :: Hash DRepKey -> Hash DRepKey -> Ordering
$c< :: Hash DRepKey -> Hash DRepKey -> Bool
< :: Hash DRepKey -> Hash DRepKey -> Bool
$c<= :: Hash DRepKey -> Hash DRepKey -> Bool
<= :: Hash DRepKey -> Hash DRepKey -> Bool
$c> :: Hash DRepKey -> Hash DRepKey -> Bool
> :: Hash DRepKey -> Hash DRepKey -> Bool
$c>= :: Hash DRepKey -> Hash DRepKey -> Bool
>= :: Hash DRepKey -> Hash DRepKey -> Bool
$cmax :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey
max :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey
$cmin :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey
min :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey
Ord)
  deriving (Int -> Hash DRepKey -> ShowS
[Hash DRepKey] -> ShowS
Hash DRepKey -> String
(Int -> Hash DRepKey -> ShowS)
-> (Hash DRepKey -> String)
-> ([Hash DRepKey] -> ShowS)
-> Show (Hash DRepKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash DRepKey -> ShowS
showsPrec :: Int -> Hash DRepKey -> ShowS
$cshow :: Hash DRepKey -> String
show :: Hash DRepKey -> String
$cshowList :: [Hash DRepKey] -> ShowS
showList :: [Hash DRepKey] -> ShowS
Show, String -> Hash DRepKey
(String -> Hash DRepKey) -> IsString (Hash DRepKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash DRepKey
fromString :: String -> Hash DRepKey
IsString) via UsingRawBytesHex (Hash DRepKey)
  deriving (Typeable (Hash DRepKey)
Typeable (Hash DRepKey) =>
(Hash DRepKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash DRepKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash DRepKey] -> Size)
-> ToCBOR (Hash DRepKey)
Hash DRepKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash DRepKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash DRepKey) -> 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
$ctoCBOR :: Hash DRepKey -> Encoding
toCBOR :: Hash DRepKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash DRepKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash DRepKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash DRepKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash DRepKey] -> Size
ToCBOR, Typeable (Hash DRepKey)
Typeable (Hash DRepKey) =>
(forall s. Decoder s (Hash DRepKey))
-> (Proxy (Hash DRepKey) -> Text) -> FromCBOR (Hash DRepKey)
Proxy (Hash DRepKey) -> Text
forall s. Decoder s (Hash DRepKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash DRepKey)
fromCBOR :: forall s. Decoder s (Hash DRepKey)
$clabel :: Proxy (Hash DRepKey) -> Text
label :: Proxy (Hash DRepKey) -> Text
FromCBOR) via UsingRawBytes (Hash DRepKey)
  deriving anyclass HasTypeProxy (Hash DRepKey)
HasTypeProxy (Hash DRepKey) =>
(Hash DRepKey -> ByteString)
-> (AsType (Hash DRepKey)
    -> ByteString -> Either DecoderError (Hash DRepKey))
-> SerialiseAsCBOR (Hash DRepKey)
AsType (Hash DRepKey)
-> ByteString -> Either DecoderError (Hash DRepKey)
Hash DRepKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash DRepKey -> ByteString
serialiseToCBOR :: Hash DRepKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash DRepKey)
-> ByteString -> Either DecoderError (Hash DRepKey)
deserialiseFromCBOR :: AsType (Hash DRepKey)
-> ByteString -> Either DecoderError (Hash DRepKey)
SerialiseAsCBOR

instance SerialiseAsRawBytes (Hash DRepKey) where
  serialiseToRawBytes :: Hash DRepKey -> ByteString
serialiseToRawBytes (DRepKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash DRepKey)
-> ByteString -> Either SerialiseAsRawBytesError (Hash DRepKey)
deserialiseFromRawBytes (AsHash AsType DRepKey
R:AsTypeDRepKey
AsDRepKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash DRepKey)
-> Either SerialiseAsRawBytesError (Hash DRepKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight
      (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash DRepKey")
      (KeyHash 'DRepRole -> Hash DRepKey
DRepKeyHash (KeyHash 'DRepRole -> Hash DRepKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'DRepRole)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash DRepKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'DRepRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash DRepKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash DRepKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs)

instance SerialiseAsBech32 (Hash DRepKey) where
  bech32PrefixFor :: Hash DRepKey -> Text
bech32PrefixFor Hash DRepKey
_ = Text
"drep"
  bech32PrefixesPermitted :: AsType (Hash DRepKey) -> [Text]
bech32PrefixesPermitted AsType (Hash DRepKey)
_ = [Text
"drep"]

instance ToJSON (Hash DRepKey) where
  toJSON :: Hash DRepKey -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (Hash DRepKey -> Text) -> Hash DRepKey -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash DRepKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32

instance ToJSONKey (Hash DRepKey) where
  toJSONKey :: ToJSONKeyFunction (Hash DRepKey)
toJSONKey = (Hash DRepKey -> Text) -> ToJSONKeyFunction (Hash DRepKey)
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText Hash DRepKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32

instance FromJSON (Hash DRepKey) where
  parseJSON :: Value -> Parser (Hash DRepKey)
parseJSON = String
-> (Text -> Parser (Hash DRepKey))
-> Value
-> Parser (Hash DRepKey)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"DRepId" ((Text -> Parser (Hash DRepKey)) -> Value -> Parser (Hash DRepKey))
-> (Text -> Parser (Hash DRepKey))
-> Value
-> Parser (Hash DRepKey)
forall a b. (a -> b) -> a -> b
$ \Text
str ->
    case AsType (Hash DRepKey)
-> Text -> Either Bech32DecodeError (Hash DRepKey)
forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 (AsType DRepKey -> AsType (Hash DRepKey)
forall a. AsType a -> AsType (Hash a)
AsHash AsType DRepKey
AsDRepKey) Text
str of
      Left Bech32DecodeError
err ->
        String -> Parser (Hash DRepKey)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (Hash DRepKey))
-> String -> Parser (Hash DRepKey)
forall a b. (a -> b) -> a -> b
$
          Doc AnsiStyle -> String
docToString (Doc AnsiStyle -> String) -> Doc AnsiStyle -> String
forall a b. (a -> b) -> a -> b
$
            [Doc AnsiStyle] -> Doc AnsiStyle
forall a. Monoid a => [a] -> a
mconcat
              [ Doc AnsiStyle
"Error deserialising Hash DRepKey: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Text
str
              , Doc AnsiStyle
" Error: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Bech32DecodeError -> Doc AnsiStyle
forall e ann. Error e => e -> Doc ann
forall ann. Bech32DecodeError -> Doc ann
prettyError Bech32DecodeError
err
              ]
      Right Hash DRepKey
h -> Hash DRepKey -> Parser (Hash DRepKey)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Hash DRepKey
h

instance HasTextEnvelope (VerificationKey DRepKey) where
  textEnvelopeType :: AsType (VerificationKey DRepKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey DRepKey)
_ =
    TextEnvelopeType
"DRepVerificationKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

instance HasTextEnvelope (SigningKey DRepKey) where
  textEnvelopeType :: AsType (SigningKey DRepKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey DRepKey)
_ =
    TextEnvelopeType
"DRepSigningKey_"
      TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
forall a. Semigroup a => a -> a -> a
<> String -> TextEnvelopeType
forall a. IsString a => String -> a
fromString (Proxy DSIGN -> String
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy DSIGN -> String
Crypto.algorithmNameDSIGN Proxy DSIGN
proxy)
   where
    proxy :: Proxy Shelley.DSIGN
    proxy :: Proxy DSIGN
proxy = Proxy DSIGN
forall {k} (t :: k). Proxy t
Proxy

---
--- Drep extended keys
---
data DRepExtendedKey

instance HasTypeProxy DRepExtendedKey where
  data AsType DRepExtendedKey = AsDRepExtendedKey
  proxyToAsType :: Proxy DRepExtendedKey -> AsType DRepExtendedKey
proxyToAsType Proxy DRepExtendedKey
_ = AsType DRepExtendedKey
AsDRepExtendedKey

instance Key DRepExtendedKey where
  newtype VerificationKey DRepExtendedKey
    = DRepExtendedVerificationKey Crypto.HD.XPub
    deriving stock VerificationKey DRepExtendedKey
-> VerificationKey DRepExtendedKey -> Bool
(VerificationKey DRepExtendedKey
 -> VerificationKey DRepExtendedKey -> Bool)
-> (VerificationKey DRepExtendedKey
    -> VerificationKey DRepExtendedKey -> Bool)
-> Eq (VerificationKey DRepExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationKey DRepExtendedKey
-> VerificationKey DRepExtendedKey -> Bool
== :: VerificationKey DRepExtendedKey
-> VerificationKey DRepExtendedKey -> Bool
$c/= :: VerificationKey DRepExtendedKey
-> VerificationKey DRepExtendedKey -> Bool
/= :: VerificationKey DRepExtendedKey
-> VerificationKey DRepExtendedKey -> Bool
Eq
    deriving anyclass HasTypeProxy (VerificationKey DRepExtendedKey)
HasTypeProxy (VerificationKey DRepExtendedKey) =>
(VerificationKey DRepExtendedKey -> ByteString)
-> (AsType (VerificationKey DRepExtendedKey)
    -> ByteString
    -> Either DecoderError (VerificationKey DRepExtendedKey))
-> SerialiseAsCBOR (VerificationKey DRepExtendedKey)
AsType (VerificationKey DRepExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey DRepExtendedKey)
VerificationKey DRepExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: VerificationKey DRepExtendedKey -> ByteString
serialiseToCBOR :: VerificationKey DRepExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (VerificationKey DRepExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey DRepExtendedKey)
deserialiseFromCBOR :: AsType (VerificationKey DRepExtendedKey)
-> ByteString
-> Either DecoderError (VerificationKey DRepExtendedKey)
SerialiseAsCBOR
    deriving (Int -> VerificationKey DRepExtendedKey -> ShowS
[VerificationKey DRepExtendedKey] -> ShowS
VerificationKey DRepExtendedKey -> String
(Int -> VerificationKey DRepExtendedKey -> ShowS)
-> (VerificationKey DRepExtendedKey -> String)
-> ([VerificationKey DRepExtendedKey] -> ShowS)
-> Show (VerificationKey DRepExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKey DRepExtendedKey -> ShowS
showsPrec :: Int -> VerificationKey DRepExtendedKey -> ShowS
$cshow :: VerificationKey DRepExtendedKey -> String
show :: VerificationKey DRepExtendedKey -> String
$cshowList :: [VerificationKey DRepExtendedKey] -> ShowS
showList :: [VerificationKey DRepExtendedKey] -> ShowS
Show, String -> VerificationKey DRepExtendedKey
(String -> VerificationKey DRepExtendedKey)
-> IsString (VerificationKey DRepExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> VerificationKey DRepExtendedKey
fromString :: String -> VerificationKey DRepExtendedKey
IsString) via UsingRawBytesHex (VerificationKey PaymentExtendedKey)

  newtype SigningKey DRepExtendedKey
    = DRepExtendedSigningKey Crypto.HD.XPrv
    deriving anyclass HasTypeProxy (SigningKey DRepExtendedKey)
HasTypeProxy (SigningKey DRepExtendedKey) =>
(SigningKey DRepExtendedKey -> ByteString)
-> (AsType (SigningKey DRepExtendedKey)
    -> ByteString -> Either DecoderError (SigningKey DRepExtendedKey))
-> SerialiseAsCBOR (SigningKey DRepExtendedKey)
AsType (SigningKey DRepExtendedKey)
-> ByteString -> Either DecoderError (SigningKey DRepExtendedKey)
SigningKey DRepExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: SigningKey DRepExtendedKey -> ByteString
serialiseToCBOR :: SigningKey DRepExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (SigningKey DRepExtendedKey)
-> ByteString -> Either DecoderError (SigningKey DRepExtendedKey)
deserialiseFromCBOR :: AsType (SigningKey DRepExtendedKey)
-> ByteString -> Either DecoderError (SigningKey DRepExtendedKey)
SerialiseAsCBOR
    deriving (Int -> SigningKey DRepExtendedKey -> ShowS
[SigningKey DRepExtendedKey] -> ShowS
SigningKey DRepExtendedKey -> String
(Int -> SigningKey DRepExtendedKey -> ShowS)
-> (SigningKey DRepExtendedKey -> String)
-> ([SigningKey DRepExtendedKey] -> ShowS)
-> Show (SigningKey DRepExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SigningKey DRepExtendedKey -> ShowS
showsPrec :: Int -> SigningKey DRepExtendedKey -> ShowS
$cshow :: SigningKey DRepExtendedKey -> String
show :: SigningKey DRepExtendedKey -> String
$cshowList :: [SigningKey DRepExtendedKey] -> ShowS
showList :: [SigningKey DRepExtendedKey] -> ShowS
Show, String -> SigningKey DRepExtendedKey
(String -> SigningKey DRepExtendedKey)
-> IsString (SigningKey DRepExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> SigningKey DRepExtendedKey
fromString :: String -> SigningKey DRepExtendedKey
IsString) via UsingRawBytesHex (SigningKey PaymentExtendedKey)

  deterministicSigningKey
    :: AsType DRepExtendedKey
    -> Crypto.Seed
    -> SigningKey DRepExtendedKey
  deterministicSigningKey :: AsType DRepExtendedKey -> Seed -> SigningKey DRepExtendedKey
deterministicSigningKey AsType DRepExtendedKey
R:AsTypeDRepExtendedKey
AsDRepExtendedKey Seed
seed =
    XPrv -> SigningKey DRepExtendedKey
DRepExtendedSigningKey
      (ByteString -> ByteString -> XPrv
forall passPhrase seed.
(ByteArrayAccess passPhrase, ByteArrayAccess seed) =>
seed -> passPhrase -> XPrv
Crypto.HD.generate ByteString
seedbs ByteString
BS.empty)
   where
    (ByteString
seedbs, Seed
_) = Word -> Seed -> (ByteString, Seed)
Crypto.getBytesFromSeedT Word
32 Seed
seed

  deterministicSigningKeySeedSize :: AsType DRepExtendedKey -> Word
  deterministicSigningKeySeedSize :: AsType DRepExtendedKey -> Word
deterministicSigningKeySeedSize AsType DRepExtendedKey
R:AsTypeDRepExtendedKey
AsDRepExtendedKey = Word
32

  getVerificationKey
    :: SigningKey DRepExtendedKey
    -> VerificationKey DRepExtendedKey
  getVerificationKey :: SigningKey DRepExtendedKey -> VerificationKey DRepExtendedKey
getVerificationKey (DRepExtendedSigningKey XPrv
sk) =
    XPub -> VerificationKey DRepExtendedKey
DRepExtendedVerificationKey (HasCallStack => XPrv -> XPub
XPrv -> XPub
Crypto.HD.toXPub XPrv
sk)

  --  We use the hash of the normal non-extended pub key so that it is
  -- consistent with the one used in addresses and signatures.
  verificationKeyHash
    :: VerificationKey DRepExtendedKey
    -> Hash DRepExtendedKey
  verificationKeyHash :: VerificationKey DRepExtendedKey -> Hash DRepExtendedKey
verificationKeyHash (DRepExtendedVerificationKey XPub
vk) =
    KeyHash 'DRepRole -> Hash DRepExtendedKey
DRepExtendedKeyHash
      (KeyHash 'DRepRole -> Hash DRepExtendedKey)
-> (Hash ADDRHASH XPub -> KeyHash 'DRepRole)
-> Hash ADDRHASH XPub
-> Hash DRepExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'DRepRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash
      (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'DRepRole)
-> (Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Hash ADDRHASH XPub
-> KeyHash 'DRepRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH XPub -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall h a b. Hash h a -> Hash h b
Crypto.castHash
      (Hash ADDRHASH XPub -> Hash DRepExtendedKey)
-> Hash ADDRHASH XPub -> Hash DRepExtendedKey
forall a b. (a -> b) -> a -> b
$ (XPub -> ByteString) -> XPub -> Hash ADDRHASH XPub
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Crypto.hashWith XPub -> ByteString
Crypto.HD.xpubPublicKey XPub
vk

newtype instance Hash DRepExtendedKey
  = DRepExtendedKeyHash {Hash DRepExtendedKey -> KeyHash 'DRepRole
unDRepExtendedKeyHash :: Shelley.KeyHash Shelley.DRepRole}
  deriving stock (Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
(Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool)
-> (Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool)
-> Eq (Hash DRepExtendedKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
== :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
$c/= :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
/= :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
Eq, Eq (Hash DRepExtendedKey)
Eq (Hash DRepExtendedKey) =>
(Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering)
-> (Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool)
-> (Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool)
-> (Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool)
-> (Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool)
-> (Hash DRepExtendedKey
    -> Hash DRepExtendedKey -> Hash DRepExtendedKey)
-> (Hash DRepExtendedKey
    -> Hash DRepExtendedKey -> Hash DRepExtendedKey)
-> Ord (Hash DRepExtendedKey)
Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering
Hash DRepExtendedKey
-> Hash DRepExtendedKey -> Hash DRepExtendedKey
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
$ccompare :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering
compare :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering
$c< :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
< :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
$c<= :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
<= :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
$c> :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
> :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
$c>= :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
>= :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool
$cmax :: Hash DRepExtendedKey
-> Hash DRepExtendedKey -> Hash DRepExtendedKey
max :: Hash DRepExtendedKey
-> Hash DRepExtendedKey -> Hash DRepExtendedKey
$cmin :: Hash DRepExtendedKey
-> Hash DRepExtendedKey -> Hash DRepExtendedKey
min :: Hash DRepExtendedKey
-> Hash DRepExtendedKey -> Hash DRepExtendedKey
Ord)
  deriving (Int -> Hash DRepExtendedKey -> ShowS
[Hash DRepExtendedKey] -> ShowS
Hash DRepExtendedKey -> String
(Int -> Hash DRepExtendedKey -> ShowS)
-> (Hash DRepExtendedKey -> String)
-> ([Hash DRepExtendedKey] -> ShowS)
-> Show (Hash DRepExtendedKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash DRepExtendedKey -> ShowS
showsPrec :: Int -> Hash DRepExtendedKey -> ShowS
$cshow :: Hash DRepExtendedKey -> String
show :: Hash DRepExtendedKey -> String
$cshowList :: [Hash DRepExtendedKey] -> ShowS
showList :: [Hash DRepExtendedKey] -> ShowS
Show, String -> Hash DRepExtendedKey
(String -> Hash DRepExtendedKey) -> IsString (Hash DRepExtendedKey)
forall a. (String -> a) -> IsString a
$cfromString :: String -> Hash DRepExtendedKey
fromString :: String -> Hash DRepExtendedKey
IsString) via UsingRawBytesHex (Hash DRepKey)
  deriving (Typeable (Hash DRepExtendedKey)
Typeable (Hash DRepExtendedKey) =>
(Hash DRepExtendedKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy (Hash DRepExtendedKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [Hash DRepExtendedKey] -> Size)
-> ToCBOR (Hash DRepExtendedKey)
Hash DRepExtendedKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash DRepExtendedKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash DRepExtendedKey) -> 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
$ctoCBOR :: Hash DRepExtendedKey -> Encoding
toCBOR :: Hash DRepExtendedKey -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash DRepExtendedKey) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash DRepExtendedKey) -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash DRepExtendedKey] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash DRepExtendedKey] -> Size
ToCBOR, Typeable (Hash DRepExtendedKey)
Typeable (Hash DRepExtendedKey) =>
(forall s. Decoder s (Hash DRepExtendedKey))
-> (Proxy (Hash DRepExtendedKey) -> Text)
-> FromCBOR (Hash DRepExtendedKey)
Proxy (Hash DRepExtendedKey) -> Text
forall s. Decoder s (Hash DRepExtendedKey)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s (Hash DRepExtendedKey)
fromCBOR :: forall s. Decoder s (Hash DRepExtendedKey)
$clabel :: Proxy (Hash DRepExtendedKey) -> Text
label :: Proxy (Hash DRepExtendedKey) -> Text
FromCBOR) via UsingRawBytes (Hash DRepKey)
  deriving anyclass HasTypeProxy (Hash DRepExtendedKey)
HasTypeProxy (Hash DRepExtendedKey) =>
(Hash DRepExtendedKey -> ByteString)
-> (AsType (Hash DRepExtendedKey)
    -> ByteString -> Either DecoderError (Hash DRepExtendedKey))
-> SerialiseAsCBOR (Hash DRepExtendedKey)
AsType (Hash DRepExtendedKey)
-> ByteString -> Either DecoderError (Hash DRepExtendedKey)
Hash DRepExtendedKey -> ByteString
forall a.
HasTypeProxy a =>
(a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
$cserialiseToCBOR :: Hash DRepExtendedKey -> ByteString
serialiseToCBOR :: Hash DRepExtendedKey -> ByteString
$cdeserialiseFromCBOR :: AsType (Hash DRepExtendedKey)
-> ByteString -> Either DecoderError (Hash DRepExtendedKey)
deserialiseFromCBOR :: AsType (Hash DRepExtendedKey)
-> ByteString -> Either DecoderError (Hash DRepExtendedKey)
SerialiseAsCBOR

instance ToCBOR (VerificationKey DRepExtendedKey) where
  toCBOR :: VerificationKey DRepExtendedKey -> Encoding
toCBOR (DRepExtendedVerificationKey XPub
xpub) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPub -> ByteString
Crypto.HD.unXPub XPub
xpub)

instance FromCBOR (VerificationKey DRepExtendedKey) where
  fromCBOR :: forall s. Decoder s (VerificationKey DRepExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (VerificationKey DRepExtendedKey))
-> (XPub -> Decoder s (VerificationKey DRepExtendedKey))
-> Either String XPub
-> Decoder s (VerificationKey DRepExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (VerificationKey DRepExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (VerificationKey DRepExtendedKey
-> Decoder s (VerificationKey DRepExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerificationKey DRepExtendedKey
 -> Decoder s (VerificationKey DRepExtendedKey))
-> (XPub -> VerificationKey DRepExtendedKey)
-> XPub
-> Decoder s (VerificationKey DRepExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey DRepExtendedKey
DRepExtendedVerificationKey)
      (ByteString -> Either String XPub
Crypto.HD.xpub (ByteString
bs :: ByteString))

instance ToCBOR (SigningKey DRepExtendedKey) where
  toCBOR :: SigningKey DRepExtendedKey -> Encoding
toCBOR (DRepExtendedSigningKey XPrv
xprv) =
    ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv)

instance FromCBOR (SigningKey DRepExtendedKey) where
  fromCBOR :: forall s. Decoder s (SigningKey DRepExtendedKey)
fromCBOR = do
    ByteString
bs <- Decoder s ByteString
forall s. Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
    (String -> Decoder s (SigningKey DRepExtendedKey))
-> (XPrv -> Decoder s (SigningKey DRepExtendedKey))
-> Either String XPrv
-> Decoder s (SigningKey DRepExtendedKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
      String -> Decoder s (SigningKey DRepExtendedKey)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
      (SigningKey DRepExtendedKey
-> Decoder s (SigningKey DRepExtendedKey)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey DRepExtendedKey
 -> Decoder s (SigningKey DRepExtendedKey))
-> (XPrv -> SigningKey DRepExtendedKey)
-> XPrv
-> Decoder s (SigningKey DRepExtendedKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey DRepExtendedKey
DRepExtendedSigningKey)
      (ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv (ByteString
bs :: ByteString))

instance SerialiseAsRawBytes (VerificationKey DRepExtendedKey) where
  serialiseToRawBytes :: VerificationKey DRepExtendedKey -> ByteString
serialiseToRawBytes (DRepExtendedVerificationKey XPub
xpub) =
    XPub -> ByteString
Crypto.HD.unXPub XPub
xpub

  deserialiseFromRawBytes :: AsType (VerificationKey DRepExtendedKey)
-> ByteString
-> Either
     SerialiseAsRawBytesError (VerificationKey DRepExtendedKey)
deserialiseFromRawBytes (AsVerificationKey AsType DRepExtendedKey
R:AsTypeDRepExtendedKey
AsDRepExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (VerificationKey DRepExtendedKey)
-> Either
     SerialiseAsRawBytesError (VerificationKey DRepExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise VerificationKey DRepExtendedKey"))
      (XPub -> VerificationKey DRepExtendedKey
DRepExtendedVerificationKey (XPub -> VerificationKey DRepExtendedKey)
-> Either String XPub
-> Either String (VerificationKey DRepExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)

instance SerialiseAsRawBytes (SigningKey DRepExtendedKey) where
  serialiseToRawBytes :: SigningKey DRepExtendedKey -> ByteString
serialiseToRawBytes (DRepExtendedSigningKey XPrv
xprv) =
    XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xprv

  deserialiseFromRawBytes :: AsType (SigningKey DRepExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (SigningKey DRepExtendedKey)
deserialiseFromRawBytes (AsSigningKey AsType DRepExtendedKey
R:AsTypeDRepExtendedKey
AsDRepExtendedKey) ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (SigningKey DRepExtendedKey)
-> Either SerialiseAsRawBytesError (SigningKey DRepExtendedKey)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first
      (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise SigningKey DRepExtendedKey"))
      (XPrv -> SigningKey DRepExtendedKey
DRepExtendedSigningKey (XPrv -> SigningKey DRepExtendedKey)
-> Either String XPrv -> Either String (SigningKey DRepExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Crypto.HD.xprv ByteString
bs)

instance SerialiseAsRawBytes (Hash DRepExtendedKey) where
  serialiseToRawBytes :: Hash DRepExtendedKey -> ByteString
serialiseToRawBytes (DRepExtendedKeyHash (Shelley.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
    Hash ADDRHASH (VerKeyDSIGN DSIGN) -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytes Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh

  deserialiseFromRawBytes :: AsType (Hash DRepExtendedKey)
-> ByteString
-> Either SerialiseAsRawBytesError (Hash DRepExtendedKey)
deserialiseFromRawBytes (AsHash AsType DRepExtendedKey
R:AsTypeDRepExtendedKey
AsDRepExtendedKey) ByteString
bs =
    SerialiseAsRawBytesError
-> Maybe (Hash DRepExtendedKey)
-> Either SerialiseAsRawBytesError (Hash DRepExtendedKey)
forall b a. b -> Maybe a -> Either b a
maybeToRight (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Hash DRepExtendedKey") (Maybe (Hash DRepExtendedKey)
 -> Either SerialiseAsRawBytesError (Hash DRepExtendedKey))
-> Maybe (Hash DRepExtendedKey)
-> Either SerialiseAsRawBytesError (Hash DRepExtendedKey)
forall a b. (a -> b) -> a -> b
$
      KeyHash 'DRepRole -> Hash DRepExtendedKey
DRepExtendedKeyHash (KeyHash 'DRepRole -> Hash DRepExtendedKey)
-> (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'DRepRole)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN)
-> Hash DRepExtendedKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'DRepRole
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Shelley.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> Hash DRepExtendedKey)
-> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
-> Maybe (Hash DRepExtendedKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Hash ADDRHASH (VerKeyDSIGN DSIGN))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Crypto.hashFromBytes ByteString
bs

instance HasTextEnvelope (VerificationKey DRepExtendedKey) where
  textEnvelopeType :: AsType (VerificationKey DRepExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey DRepExtendedKey)
_ = TextEnvelopeType
"DRepExtendedVerificationKey_ed25519_bip32"

instance HasTextEnvelope (SigningKey DRepExtendedKey) where
  textEnvelopeType :: AsType (SigningKey DRepExtendedKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey DRepExtendedKey)
_ = TextEnvelopeType
"DRepExtendedSigningKey_ed25519_bip32"

instance SerialiseAsBech32 (VerificationKey DRepExtendedKey) where
  bech32PrefixFor :: VerificationKey DRepExtendedKey -> Text
bech32PrefixFor VerificationKey DRepExtendedKey
_ = Text
"drep_xvk"
  bech32PrefixesPermitted :: AsType (VerificationKey DRepExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (VerificationKey DRepExtendedKey)
_ = [Text
"drep_xvk"]

instance SerialiseAsBech32 (SigningKey DRepExtendedKey) where
  bech32PrefixFor :: SigningKey DRepExtendedKey -> Text
bech32PrefixFor SigningKey DRepExtendedKey
_ = Text
"drep_xsk"
  bech32PrefixesPermitted :: AsType (SigningKey DRepExtendedKey) -> [Text]
bech32PrefixesPermitted AsType (SigningKey DRepExtendedKey)
_ = [Text
"drep_xsk"]

instance CastVerificationKeyRole DRepExtendedKey DRepKey where
  castVerificationKey :: VerificationKey DRepExtendedKey -> VerificationKey DRepKey
castVerificationKey (DRepExtendedVerificationKey XPub
vk) =
    VKey 'DRepRole -> VerificationKey DRepKey
DRepVerificationKey
      (VKey 'DRepRole -> VerificationKey DRepKey)
-> (XPub -> VKey 'DRepRole) -> XPub -> VerificationKey DRepKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> VKey 'DRepRole
forall (kd :: KeyRole). VerKeyDSIGN DSIGN -> VKey kd
Shelley.VKey
      (VerKeyDSIGN DSIGN -> VKey 'DRepRole)
-> (XPub -> VerKeyDSIGN DSIGN) -> XPub -> VKey 'DRepRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerKeyDSIGN DSIGN -> Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN
forall a. a -> Maybe a -> a
fromMaybe VerKeyDSIGN DSIGN
forall {a}. a
impossible
      (Maybe (VerKeyDSIGN DSIGN) -> VerKeyDSIGN DSIGN)
-> (XPub -> Maybe (VerKeyDSIGN DSIGN)) -> XPub -> VerKeyDSIGN DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (VerKeyDSIGN DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
Crypto.rawDeserialiseVerKeyDSIGN
      (ByteString -> Maybe (VerKeyDSIGN DSIGN))
-> (XPub -> ByteString) -> XPub -> Maybe (VerKeyDSIGN DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> ByteString
Crypto.HD.xpubPublicKey
      (XPub -> VerificationKey DRepKey)
-> XPub -> VerificationKey DRepKey
forall a b. (a -> b) -> a -> b
$ XPub
vk
   where
    impossible :: a
impossible =
      String -> a
forall a. HasCallStack => String -> a
error String
"castVerificationKey (DRep): byron and shelley key sizes do not match!"