{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}

module Cardano.Ledger.Keys
  ( KeyRole (..),
    HasKeyRole (..),
    asWitness,

    -- * DSIGN
    DSignable,
    VKey (..),
    KeyPair (..),
    signedDSIGN,
    verifySignedDSIGN,
    hashSignature,

    -- * Key hashes
    KeyHash (..),
    hashKey,

    -- * Genesis delegations
    GenDelegPair (..),
    GenDelegs (..),
    GKeys (..),

    -- * KES
    KESignable,

    -- * VRF
    VRFSignable,

    -- * Re-exports from cardano-crypto-class
    DSIGN.decodeSignedDSIGN,
    DSIGN.encodeSignedDSIGN,
    Hash.hashWithSerialiser,
    KES.decodeSignedKES,
    KES.decodeVerKeyKES,
    KES.encodeSignedKES,
    KES.encodeVerKeyKES,
    KES.signedKES,
    KES.updateKES,
    KES.verifyKES,
    KES.verifySignedKES,
    VRF.decodeVerKeyVRF,
    VRF.encodeVerKeyVRF,
    VRF.hashVerKeyVRF,
    VRF.verifyVRF,

    -- * Re-parametrised types over `crypto`
    CertifiedVRF,
    Hash,
    SignedDSIGN,
    SignKeyDSIGN,
    SignedKES,
    SignKeyKES,
    SignKeyVRF,
    VerKeyKES,
    VerKeyVRF,
  )
where

import Cardano.Binary (FromCBOR (..), ToCBOR (..), encodeListLen)
import qualified Cardano.Crypto.DSIGN as DSIGN
import qualified Cardano.Crypto.Hash as Hash
import qualified Cardano.Crypto.KES as KES
import qualified Cardano.Crypto.VRF as VRF
import Cardano.Ledger.Crypto (ADDRHASH, Crypto, DSIGN, HASH, KES, VRF)
import Cardano.Ledger.Serialization (decodeRecordNamed)
import Control.DeepSeq (NFData)
import Data.Aeson (FromJSON (..), FromJSONKey, ToJSON (..), ToJSONKey, (.:), (.=))
import qualified Data.Aeson as Aeson
import Data.Coerce (Coercible, coerce)
import Data.Kind (Type)
import Data.Map.Strict (Map)
import Data.Set (Set)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
import Quiet

-- | The role of a key.
--
--   Note that a role is not _fixed_, nor is it unique. In particular, keys may
--   variously be used as witnesses, and so in many case we will change the role
--   of a key to the 'Witness' role.
--
--   It is also perfectly allowable for a key to be used in many roles; there is
--   nothing prohibiting somebody using the same underlying key as their payment
--   and staking key, as well as the key for their stake pool. So these roles
--   are more intended for two purposes:
--
--   - To make explicit how we are using a key in the specifications
--   - To provide a guide to downstream implementors, for whom the profusion of
--     keys may be confusing.
data KeyRole
  = Genesis
  | GenesisDelegate
  | Payment
  | Staking
  | StakePool
  | BlockIssuer
  | Witness
  deriving (Int -> KeyRole -> ShowS
[KeyRole] -> ShowS
KeyRole -> String
(Int -> KeyRole -> ShowS)
-> (KeyRole -> String) -> ([KeyRole] -> ShowS) -> Show KeyRole
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyRole] -> ShowS
$cshowList :: [KeyRole] -> ShowS
show :: KeyRole -> String
$cshow :: KeyRole -> String
showsPrec :: Int -> KeyRole -> ShowS
$cshowsPrec :: Int -> KeyRole -> ShowS
Show)

class HasKeyRole (a :: KeyRole -> Type -> Type) where
  -- | General coercion of key roles.
  --
  --   The presence of this function is mostly to help the user realise where they
  --   are converting key roles.
  coerceKeyRole ::
    a r crypto ->
    a r' crypto
  default coerceKeyRole ::
    Coercible (a r crypto) (a r' crypto) =>
    a r crypto ->
    a r' crypto
  coerceKeyRole = a r crypto -> a r' crypto
coerce

-- | Use a key as a witness.
--
--   This is the most common coercion between key roles, because most keys can
--   be used as witnesses to some types of transaction. As such, we provide an
--   explicit coercion for it.
asWitness ::
  (HasKeyRole a) =>
  a r crypto ->
  a 'Witness crypto
asWitness :: a r crypto -> a 'Witness crypto
asWitness = a r crypto -> a 'Witness crypto
forall (a :: KeyRole -> * -> *) (r :: KeyRole) crypto
       (r' :: KeyRole).
HasKeyRole a =>
a r crypto -> a r' crypto
coerceKeyRole

--------------------------------------------------------------------------------
-- Verification keys
--------------------------------------------------------------------------------

type DSignable c = DSIGN.Signable (DSIGN c)

-- | Discriminated verification key
--
--   We wrap the basic `VerKeyDSIGN` in order to add the key role.
newtype VKey (kd :: KeyRole) crypto = VKey {VKey kd crypto -> VerKeyDSIGN (DSIGN crypto)
unVKey :: DSIGN.VerKeyDSIGN (DSIGN crypto)}
  deriving ((forall x. VKey kd crypto -> Rep (VKey kd crypto) x)
-> (forall x. Rep (VKey kd crypto) x -> VKey kd crypto)
-> Generic (VKey kd crypto)
forall x. Rep (VKey kd crypto) x -> VKey kd crypto
forall x. VKey kd crypto -> Rep (VKey kd crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (kd :: KeyRole) crypto x.
Rep (VKey kd crypto) x -> VKey kd crypto
forall (kd :: KeyRole) crypto x.
VKey kd crypto -> Rep (VKey kd crypto) x
$cto :: forall (kd :: KeyRole) crypto x.
Rep (VKey kd crypto) x -> VKey kd crypto
$cfrom :: forall (kd :: KeyRole) crypto x.
VKey kd crypto -> Rep (VKey kd crypto) x
Generic)

deriving via Quiet (VKey kd crypto) instance Crypto crypto => Show (VKey kd crypto)

deriving instance Crypto crypto => Eq (VKey kd crypto)

deriving instance
  (Crypto crypto, NFData (DSIGN.VerKeyDSIGN (DSIGN crypto))) =>
  NFData (VKey kd crypto)

deriving instance Crypto crypto => NoThunks (VKey kd crypto)

instance HasKeyRole VKey

instance
  (Crypto crypto, Typeable kd) =>
  FromCBOR (VKey kd crypto)
  where
  fromCBOR :: Decoder s (VKey kd crypto)
fromCBOR = VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
forall (kd :: KeyRole) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
VKey (VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto)
-> Decoder s (VerKeyDSIGN (DSIGN crypto))
-> Decoder s (VKey kd crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (VerKeyDSIGN (DSIGN crypto))
forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
DSIGN.decodeVerKeyDSIGN

instance
  (Crypto crypto, Typeable kd) =>
  ToCBOR (VKey kd crypto)
  where
  toCBOR :: VKey kd crypto -> Encoding
toCBOR (VKey VerKeyDSIGN (DSIGN crypto)
vk) = VerKeyDSIGN (DSIGN crypto) -> Encoding
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> Encoding
DSIGN.encodeVerKeyDSIGN VerKeyDSIGN (DSIGN crypto)
vk
  encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VKey kd crypto) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_size Proxy (VKey kd crypto)
proxy = Proxy (VerKeyDSIGN (DSIGN crypto)) -> Size
forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
DSIGN.encodedVerKeyDSIGNSizeExpr ((\(VKey VerKeyDSIGN (DSIGN crypto)
k) -> VerKeyDSIGN (DSIGN crypto)
k) (VKey kd crypto -> VerKeyDSIGN (DSIGN crypto))
-> Proxy (VKey kd crypto) -> Proxy (VerKeyDSIGN (DSIGN crypto))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (VKey kd crypto)
proxy)

-- | Pair of signing key and verification key, with a usage role.
data KeyPair (kd :: KeyRole) crypto = KeyPair
  { KeyPair kd crypto -> VKey kd crypto
vKey :: !(VKey kd crypto),
    KeyPair kd crypto -> SignKeyDSIGN (DSIGN crypto)
sKey :: !(DSIGN.SignKeyDSIGN (DSIGN crypto))
  }
  deriving ((forall x. KeyPair kd crypto -> Rep (KeyPair kd crypto) x)
-> (forall x. Rep (KeyPair kd crypto) x -> KeyPair kd crypto)
-> Generic (KeyPair kd crypto)
forall x. Rep (KeyPair kd crypto) x -> KeyPair kd crypto
forall x. KeyPair kd crypto -> Rep (KeyPair kd crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (kd :: KeyRole) crypto x.
Rep (KeyPair kd crypto) x -> KeyPair kd crypto
forall (kd :: KeyRole) crypto x.
KeyPair kd crypto -> Rep (KeyPair kd crypto) x
$cto :: forall (kd :: KeyRole) crypto x.
Rep (KeyPair kd crypto) x -> KeyPair kd crypto
$cfrom :: forall (kd :: KeyRole) crypto x.
KeyPair kd crypto -> Rep (KeyPair kd crypto) x
Generic, Int -> KeyPair kd crypto -> ShowS
[KeyPair kd crypto] -> ShowS
KeyPair kd crypto -> String
(Int -> KeyPair kd crypto -> ShowS)
-> (KeyPair kd crypto -> String)
-> ([KeyPair kd crypto] -> ShowS)
-> Show (KeyPair kd crypto)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (kd :: KeyRole) crypto.
Crypto crypto =>
Int -> KeyPair kd crypto -> ShowS
forall (kd :: KeyRole) crypto.
Crypto crypto =>
[KeyPair kd crypto] -> ShowS
forall (kd :: KeyRole) crypto.
Crypto crypto =>
KeyPair kd crypto -> String
showList :: [KeyPair kd crypto] -> ShowS
$cshowList :: forall (kd :: KeyRole) crypto.
Crypto crypto =>
[KeyPair kd crypto] -> ShowS
show :: KeyPair kd crypto -> String
$cshow :: forall (kd :: KeyRole) crypto.
Crypto crypto =>
KeyPair kd crypto -> String
showsPrec :: Int -> KeyPair kd crypto -> ShowS
$cshowsPrec :: forall (kd :: KeyRole) crypto.
Crypto crypto =>
Int -> KeyPair kd crypto -> ShowS
Show)

instance
  ( Crypto crypto,
    NFData (DSIGN.VerKeyDSIGN (DSIGN crypto)),
    NFData (DSIGN.SignKeyDSIGN (DSIGN crypto))
  ) =>
  NFData (KeyPair kd crypto)

instance Crypto crypto => NoThunks (KeyPair kd crypto)

instance HasKeyRole KeyPair

-- | Produce a digital signature
signedDSIGN ::
  (Crypto crypto, DSIGN.Signable (DSIGN crypto) a) =>
  DSIGN.SignKeyDSIGN (DSIGN crypto) ->
  a ->
  SignedDSIGN crypto a
signedDSIGN :: SignKeyDSIGN (DSIGN crypto) -> a -> SignedDSIGN crypto a
signedDSIGN SignKeyDSIGN (DSIGN crypto)
key a
a = ContextDSIGN (DSIGN crypto)
-> a -> SignKeyDSIGN (DSIGN crypto) -> SignedDSIGN crypto a
forall v a.
(DSIGNAlgorithm v, Signable v a) =>
ContextDSIGN v -> a -> SignKeyDSIGN v -> SignedDSIGN v a
DSIGN.signedDSIGN () a
a SignKeyDSIGN (DSIGN crypto)
key

-- | Verify a digital signature
verifySignedDSIGN ::
  (Crypto crypto, DSIGN.Signable (DSIGN crypto) a) =>
  VKey kd crypto ->
  a ->
  SignedDSIGN crypto a ->
  Bool
verifySignedDSIGN :: VKey kd crypto -> a -> SignedDSIGN crypto a -> Bool
verifySignedDSIGN (VKey VerKeyDSIGN (DSIGN crypto)
vk) a
vd SignedDSIGN crypto a
sigDSIGN =
  (String -> Bool) -> (() -> Bool) -> Either String () -> Bool
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Bool -> String -> Bool
forall a b. a -> b -> a
const Bool
False) (Bool -> () -> Bool
forall a b. a -> b -> a
const Bool
True) (Either String () -> Bool) -> Either String () -> Bool
forall a b. (a -> b) -> a -> b
$ ContextDSIGN (DSIGN crypto)
-> VerKeyDSIGN (DSIGN crypto)
-> a
-> SignedDSIGN crypto a
-> Either String ()
forall v a.
(DSIGNAlgorithm v, Signable v a, HasCallStack) =>
ContextDSIGN v
-> VerKeyDSIGN v -> a -> SignedDSIGN v a -> Either String ()
DSIGN.verifySignedDSIGN () VerKeyDSIGN (DSIGN crypto)
vk a
vd SignedDSIGN crypto a
sigDSIGN

-- | Hash a given signature
hashSignature ::
  (Crypto crypto) =>
  SignedDSIGN crypto (Hash crypto h) ->
  Hash crypto (SignedDSIGN crypto (Hash crypto h))
hashSignature :: SignedDSIGN crypto (Hash crypto h)
-> Hash crypto (SignedDSIGN crypto (Hash crypto h))
hashSignature = (SignedDSIGN crypto (Hash crypto h) -> ByteString)
-> SignedDSIGN crypto (Hash crypto h)
-> Hash crypto (SignedDSIGN crypto (Hash crypto h))
forall h a. HashAlgorithm h => (a -> ByteString) -> a -> Hash h a
Hash.hashWith (SigDSIGN (DSIGN crypto) -> ByteString
forall v. DSIGNAlgorithm v => SigDSIGN v -> ByteString
DSIGN.rawSerialiseSigDSIGN (SigDSIGN (DSIGN crypto) -> ByteString)
-> (SignedDSIGN crypto (Hash crypto h) -> SigDSIGN (DSIGN crypto))
-> SignedDSIGN crypto (Hash crypto h)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignedDSIGN crypto (Hash crypto h) -> SigDSIGN (DSIGN crypto)
coerce)

--------------------------------------------------------------------------------
-- Key Hashes
--------------------------------------------------------------------------------

-- | Discriminated hash of public Key
newtype KeyHash (discriminator :: KeyRole) crypto
  = KeyHash (Hash.Hash (ADDRHASH crypto) (DSIGN.VerKeyDSIGN (DSIGN crypto)))
  deriving (Int -> KeyHash discriminator crypto -> ShowS
[KeyHash discriminator crypto] -> ShowS
KeyHash discriminator crypto -> String
(Int -> KeyHash discriminator crypto -> ShowS)
-> (KeyHash discriminator crypto -> String)
-> ([KeyHash discriminator crypto] -> ShowS)
-> Show (KeyHash discriminator crypto)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (discriminator :: KeyRole) crypto.
Int -> KeyHash discriminator crypto -> ShowS
forall (discriminator :: KeyRole) crypto.
[KeyHash discriminator crypto] -> ShowS
forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto -> String
showList :: [KeyHash discriminator crypto] -> ShowS
$cshowList :: forall (discriminator :: KeyRole) crypto.
[KeyHash discriminator crypto] -> ShowS
show :: KeyHash discriminator crypto -> String
$cshow :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto -> String
showsPrec :: Int -> KeyHash discriminator crypto -> ShowS
$cshowsPrec :: forall (discriminator :: KeyRole) crypto.
Int -> KeyHash discriminator crypto -> ShowS
Show, KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
(KeyHash discriminator crypto
 -> KeyHash discriminator crypto -> Bool)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> Bool)
-> Eq (KeyHash discriminator crypto)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
/= :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
$c/= :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
== :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
$c== :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
Eq, Eq (KeyHash discriminator crypto)
Eq (KeyHash discriminator crypto)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> Ordering)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> Bool)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> Bool)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> Bool)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> Bool)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> KeyHash discriminator crypto)
-> (KeyHash discriminator crypto
    -> KeyHash discriminator crypto -> KeyHash discriminator crypto)
-> Ord (KeyHash discriminator crypto)
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Ordering
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> KeyHash discriminator crypto
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (discriminator :: KeyRole) crypto.
Eq (KeyHash discriminator crypto)
forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Ordering
forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> KeyHash discriminator crypto
min :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> KeyHash discriminator crypto
$cmin :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> KeyHash discriminator crypto
max :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> KeyHash discriminator crypto
$cmax :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> KeyHash discriminator crypto
>= :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
$c>= :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
> :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
$c> :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
<= :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
$c<= :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
< :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
$c< :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Bool
compare :: KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Ordering
$ccompare :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto
-> KeyHash discriminator crypto -> Ordering
$cp1Ord :: forall (discriminator :: KeyRole) crypto.
Eq (KeyHash discriminator crypto)
Ord)
  deriving newtype (KeyHash discriminator crypto -> ()
(KeyHash discriminator crypto -> ())
-> NFData (KeyHash discriminator crypto)
forall a. (a -> ()) -> NFData a
forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto -> ()
rnf :: KeyHash discriminator crypto -> ()
$crnf :: forall (discriminator :: KeyRole) crypto.
KeyHash discriminator crypto -> ()
NFData, Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo)
Proxy (KeyHash discriminator crypto) -> String
(Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo))
-> (Context
    -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo))
-> (Proxy (KeyHash discriminator crypto) -> String)
-> NoThunks (KeyHash discriminator crypto)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (discriminator :: KeyRole) crypto.
Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo)
forall (discriminator :: KeyRole) crypto.
Proxy (KeyHash discriminator crypto) -> String
showTypeOf :: Proxy (KeyHash discriminator crypto) -> String
$cshowTypeOf :: forall (discriminator :: KeyRole) crypto.
Proxy (KeyHash discriminator crypto) -> String
wNoThunks :: Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (discriminator :: KeyRole) crypto.
Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo)
noThunks :: Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (discriminator :: KeyRole) crypto.
Context -> KeyHash discriminator crypto -> IO (Maybe ThunkInfo)
NoThunks, Rep (KeyHash discriminator crypto) x
-> KeyHash discriminator crypto
KeyHash discriminator crypto
-> Rep (KeyHash discriminator crypto) x
(forall x.
 KeyHash discriminator crypto
 -> Rep (KeyHash discriminator crypto) x)
-> (forall x.
    Rep (KeyHash discriminator crypto) x
    -> KeyHash discriminator crypto)
-> Generic (KeyHash discriminator crypto)
forall x.
Rep (KeyHash discriminator crypto) x
-> KeyHash discriminator crypto
forall x.
KeyHash discriminator crypto
-> Rep (KeyHash discriminator crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (discriminator :: KeyRole) crypto x.
Rep (KeyHash discriminator crypto) x
-> KeyHash discriminator crypto
forall (discriminator :: KeyRole) crypto x.
KeyHash discriminator crypto
-> Rep (KeyHash discriminator crypto) x
to :: Rep (KeyHash discriminator crypto) x
-> KeyHash discriminator crypto
$cto :: forall (discriminator :: KeyRole) crypto x.
Rep (KeyHash discriminator crypto) x
-> KeyHash discriminator crypto
from :: KeyHash discriminator crypto
-> Rep (KeyHash discriminator crypto) x
$cfrom :: forall (discriminator :: KeyRole) crypto x.
KeyHash discriminator crypto
-> Rep (KeyHash discriminator crypto) x
Generic)

deriving instance
  (Crypto crypto, Typeable disc) =>
  ToCBOR (KeyHash disc crypto)

deriving instance
  (Crypto crypto, Typeable disc) =>
  FromCBOR (KeyHash disc crypto)

deriving newtype instance
  Crypto crypto =>
  ToJSONKey (KeyHash disc crypto)

deriving newtype instance
  Crypto crypto =>
  FromJSONKey (KeyHash disc crypto)

deriving newtype instance
  Crypto crypto =>
  ToJSON (KeyHash disc crypto)

deriving newtype instance
  Crypto crypto =>
  FromJSON (KeyHash disc crypto)

instance HasKeyRole KeyHash

-- | Hash a given public key
hashKey ::
  ( Crypto crypto
  ) =>
  VKey kd crypto ->
  KeyHash kd crypto
hashKey :: VKey kd crypto -> KeyHash kd crypto
hashKey (VKey VerKeyDSIGN (DSIGN crypto)
vk) = Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash kd crypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
KeyHash (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
 -> KeyHash kd crypto)
-> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash kd crypto
forall a b. (a -> b) -> a -> b
$ VerKeyDSIGN (DSIGN crypto)
-> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
forall v h.
(DSIGNAlgorithm v, HashAlgorithm h) =>
VerKeyDSIGN v -> Hash h (VerKeyDSIGN v)
DSIGN.hashVerKeyDSIGN VerKeyDSIGN (DSIGN crypto)
vk

--------------------------------------------------------------------------------
-- KES
--------------------------------------------------------------------------------

type KESignable c = KES.Signable (KES c)

--------------------------------------------------------------------------------
-- VRF
--------------------------------------------------------------------------------

type VRFSignable c = VRF.Signable (VRF c)

--------------------------------------------------------------------------------
-- Genesis delegation
--
-- TODO should this really live in here?
--------------------------------------------------------------------------------

data GenDelegPair crypto = GenDelegPair
  { GenDelegPair crypto -> KeyHash 'GenesisDelegate crypto
genDelegKeyHash :: !(KeyHash 'GenesisDelegate crypto),
    GenDelegPair crypto -> Hash crypto (VerKeyVRF crypto)
genDelegVrfHash :: !(Hash crypto (VerKeyVRF crypto))
  }
  deriving (Int -> GenDelegPair crypto -> ShowS
[GenDelegPair crypto] -> ShowS
GenDelegPair crypto -> String
(Int -> GenDelegPair crypto -> ShowS)
-> (GenDelegPair crypto -> String)
-> ([GenDelegPair crypto] -> ShowS)
-> Show (GenDelegPair crypto)
forall crypto. Int -> GenDelegPair crypto -> ShowS
forall crypto. [GenDelegPair crypto] -> ShowS
forall crypto. GenDelegPair crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenDelegPair crypto] -> ShowS
$cshowList :: forall crypto. [GenDelegPair crypto] -> ShowS
show :: GenDelegPair crypto -> String
$cshow :: forall crypto. GenDelegPair crypto -> String
showsPrec :: Int -> GenDelegPair crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> GenDelegPair crypto -> ShowS
Show, GenDelegPair crypto -> GenDelegPair crypto -> Bool
(GenDelegPair crypto -> GenDelegPair crypto -> Bool)
-> (GenDelegPair crypto -> GenDelegPair crypto -> Bool)
-> Eq (GenDelegPair crypto)
forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenDelegPair crypto -> GenDelegPair crypto -> Bool
$c/= :: forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
== :: GenDelegPair crypto -> GenDelegPair crypto -> Bool
$c== :: forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
Eq, Eq (GenDelegPair crypto)
Eq (GenDelegPair crypto)
-> (GenDelegPair crypto -> GenDelegPair crypto -> Ordering)
-> (GenDelegPair crypto -> GenDelegPair crypto -> Bool)
-> (GenDelegPair crypto -> GenDelegPair crypto -> Bool)
-> (GenDelegPair crypto -> GenDelegPair crypto -> Bool)
-> (GenDelegPair crypto -> GenDelegPair crypto -> Bool)
-> (GenDelegPair crypto
    -> GenDelegPair crypto -> GenDelegPair crypto)
-> (GenDelegPair crypto
    -> GenDelegPair crypto -> GenDelegPair crypto)
-> Ord (GenDelegPair crypto)
GenDelegPair crypto -> GenDelegPair crypto -> Bool
GenDelegPair crypto -> GenDelegPair crypto -> Ordering
GenDelegPair crypto -> GenDelegPair crypto -> GenDelegPair crypto
forall crypto. Eq (GenDelegPair crypto)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
forall crypto.
GenDelegPair crypto -> GenDelegPair crypto -> Ordering
forall crypto.
GenDelegPair crypto -> GenDelegPair crypto -> GenDelegPair crypto
min :: GenDelegPair crypto -> GenDelegPair crypto -> GenDelegPair crypto
$cmin :: forall crypto.
GenDelegPair crypto -> GenDelegPair crypto -> GenDelegPair crypto
max :: GenDelegPair crypto -> GenDelegPair crypto -> GenDelegPair crypto
$cmax :: forall crypto.
GenDelegPair crypto -> GenDelegPair crypto -> GenDelegPair crypto
>= :: GenDelegPair crypto -> GenDelegPair crypto -> Bool
$c>= :: forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
> :: GenDelegPair crypto -> GenDelegPair crypto -> Bool
$c> :: forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
<= :: GenDelegPair crypto -> GenDelegPair crypto -> Bool
$c<= :: forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
< :: GenDelegPair crypto -> GenDelegPair crypto -> Bool
$c< :: forall crypto. GenDelegPair crypto -> GenDelegPair crypto -> Bool
compare :: GenDelegPair crypto -> GenDelegPair crypto -> Ordering
$ccompare :: forall crypto.
GenDelegPair crypto -> GenDelegPair crypto -> Ordering
$cp1Ord :: forall crypto. Eq (GenDelegPair crypto)
Ord, (forall x. GenDelegPair crypto -> Rep (GenDelegPair crypto) x)
-> (forall x. Rep (GenDelegPair crypto) x -> GenDelegPair crypto)
-> Generic (GenDelegPair crypto)
forall x. Rep (GenDelegPair crypto) x -> GenDelegPair crypto
forall x. GenDelegPair crypto -> Rep (GenDelegPair crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (GenDelegPair crypto) x -> GenDelegPair crypto
forall crypto x. GenDelegPair crypto -> Rep (GenDelegPair crypto) x
$cto :: forall crypto x. Rep (GenDelegPair crypto) x -> GenDelegPair crypto
$cfrom :: forall crypto x. GenDelegPair crypto -> Rep (GenDelegPair crypto) x
Generic)

instance NoThunks (GenDelegPair crypto)

instance NFData (GenDelegPair crypto)

instance Crypto crypto => ToCBOR (GenDelegPair crypto) where
  toCBOR :: GenDelegPair crypto -> Encoding
toCBOR (GenDelegPair KeyHash 'GenesisDelegate crypto
hk Hash crypto (VerKeyVRF crypto)
vrf) =
    Word -> Encoding
encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> KeyHash 'GenesisDelegate crypto -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR KeyHash 'GenesisDelegate crypto
hk Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Hash crypto (VerKeyVRF crypto) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Hash crypto (VerKeyVRF crypto)
vrf

instance Crypto crypto => FromCBOR (GenDelegPair crypto) where
  fromCBOR :: Decoder s (GenDelegPair crypto)
fromCBOR = do
    Text
-> (GenDelegPair crypto -> Int)
-> Decoder s (GenDelegPair crypto)
-> Decoder s (GenDelegPair crypto)
forall a s. Text -> (a -> Int) -> Decoder s a -> Decoder s a
decodeRecordNamed
      Text
"GenDelegPair"
      (Int -> GenDelegPair crypto -> Int
forall a b. a -> b -> a
const Int
2)
      (KeyHash 'GenesisDelegate crypto
-> Hash (HASH crypto) (VerKeyVRF (VRF crypto))
-> GenDelegPair crypto
forall crypto.
KeyHash 'GenesisDelegate crypto
-> Hash crypto (VerKeyVRF crypto) -> GenDelegPair crypto
GenDelegPair (KeyHash 'GenesisDelegate crypto
 -> Hash (HASH crypto) (VerKeyVRF (VRF crypto))
 -> GenDelegPair crypto)
-> Decoder s (KeyHash 'GenesisDelegate crypto)
-> Decoder
     s
     (Hash (HASH crypto) (VerKeyVRF (VRF crypto))
      -> GenDelegPair crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (KeyHash 'GenesisDelegate crypto)
forall a s. FromCBOR a => Decoder s a
fromCBOR Decoder
  s
  (Hash (HASH crypto) (VerKeyVRF (VRF crypto))
   -> GenDelegPair crypto)
-> Decoder s (Hash (HASH crypto) (VerKeyVRF (VRF crypto)))
-> Decoder s (GenDelegPair crypto)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s (Hash (HASH crypto) (VerKeyVRF (VRF crypto)))
forall a s. FromCBOR a => Decoder s a
fromCBOR)

instance Crypto crypto => ToJSON (GenDelegPair crypto) where
  toJSON :: GenDelegPair crypto -> Value
toJSON (GenDelegPair KeyHash 'GenesisDelegate crypto
d Hash crypto (VerKeyVRF crypto)
v) =
    [Pair] -> Value
Aeson.object
      [ Key
"delegate" Key -> KeyHash 'GenesisDelegate crypto -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= KeyHash 'GenesisDelegate crypto
d,
        Key
"vrf" Key -> Hash crypto (VerKeyVRF crypto) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Hash crypto (VerKeyVRF crypto)
v
      ]

instance Crypto crypto => FromJSON (GenDelegPair crypto) where
  parseJSON :: Value -> Parser (GenDelegPair crypto)
parseJSON =
    String
-> (Object -> Parser (GenDelegPair crypto))
-> Value
-> Parser (GenDelegPair crypto)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"GenDelegPair" ((Object -> Parser (GenDelegPair crypto))
 -> Value -> Parser (GenDelegPair crypto))
-> (Object -> Parser (GenDelegPair crypto))
-> Value
-> Parser (GenDelegPair crypto)
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
      KeyHash 'GenesisDelegate crypto
-> Hash (HASH crypto) (VerKeyVRF (VRF crypto))
-> GenDelegPair crypto
forall crypto.
KeyHash 'GenesisDelegate crypto
-> Hash crypto (VerKeyVRF crypto) -> GenDelegPair crypto
GenDelegPair
        (KeyHash 'GenesisDelegate crypto
 -> Hash (HASH crypto) (VerKeyVRF (VRF crypto))
 -> GenDelegPair crypto)
-> Parser (KeyHash 'GenesisDelegate crypto)
-> Parser
     (Hash (HASH crypto) (VerKeyVRF (VRF crypto))
      -> GenDelegPair crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser (KeyHash 'GenesisDelegate crypto)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"delegate"
        Parser
  (Hash (HASH crypto) (VerKeyVRF (VRF crypto))
   -> GenDelegPair crypto)
-> Parser (Hash (HASH crypto) (VerKeyVRF (VRF crypto)))
-> Parser (GenDelegPair crypto)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object
-> Key -> Parser (Hash (HASH crypto) (VerKeyVRF (VRF crypto)))
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"vrf"

newtype GenDelegs crypto = GenDelegs
  { GenDelegs crypto
-> Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
unGenDelegs :: Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
  }
  deriving (GenDelegs crypto -> GenDelegs crypto -> Bool
(GenDelegs crypto -> GenDelegs crypto -> Bool)
-> (GenDelegs crypto -> GenDelegs crypto -> Bool)
-> Eq (GenDelegs crypto)
forall crypto. GenDelegs crypto -> GenDelegs crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenDelegs crypto -> GenDelegs crypto -> Bool
$c/= :: forall crypto. GenDelegs crypto -> GenDelegs crypto -> Bool
== :: GenDelegs crypto -> GenDelegs crypto -> Bool
$c== :: forall crypto. GenDelegs crypto -> GenDelegs crypto -> Bool
Eq, Typeable (GenDelegs crypto)
Decoder s (GenDelegs crypto)
Typeable (GenDelegs crypto)
-> (forall s. Decoder s (GenDelegs crypto))
-> (Proxy (GenDelegs crypto) -> Text)
-> FromCBOR (GenDelegs crypto)
Proxy (GenDelegs crypto) -> Text
forall s. Decoder s (GenDelegs crypto)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
forall crypto. Crypto crypto => Typeable (GenDelegs crypto)
forall crypto. Crypto crypto => Proxy (GenDelegs crypto) -> Text
forall crypto s. Crypto crypto => Decoder s (GenDelegs crypto)
label :: Proxy (GenDelegs crypto) -> Text
$clabel :: forall crypto. Crypto crypto => Proxy (GenDelegs crypto) -> Text
fromCBOR :: Decoder s (GenDelegs crypto)
$cfromCBOR :: forall crypto s. Crypto crypto => Decoder s (GenDelegs crypto)
$cp1FromCBOR :: forall crypto. Crypto crypto => Typeable (GenDelegs crypto)
FromCBOR, Context -> GenDelegs crypto -> IO (Maybe ThunkInfo)
Proxy (GenDelegs crypto) -> String
(Context -> GenDelegs crypto -> IO (Maybe ThunkInfo))
-> (Context -> GenDelegs crypto -> IO (Maybe ThunkInfo))
-> (Proxy (GenDelegs crypto) -> String)
-> NoThunks (GenDelegs crypto)
forall crypto. Context -> GenDelegs crypto -> IO (Maybe ThunkInfo)
forall crypto. Proxy (GenDelegs crypto) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (GenDelegs crypto) -> String
$cshowTypeOf :: forall crypto. Proxy (GenDelegs crypto) -> String
wNoThunks :: Context -> GenDelegs crypto -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall crypto. Context -> GenDelegs crypto -> IO (Maybe ThunkInfo)
noThunks :: Context -> GenDelegs crypto -> IO (Maybe ThunkInfo)
$cnoThunks :: forall crypto. Context -> GenDelegs crypto -> IO (Maybe ThunkInfo)
NoThunks, GenDelegs crypto -> ()
(GenDelegs crypto -> ()) -> NFData (GenDelegs crypto)
forall crypto. GenDelegs crypto -> ()
forall a. (a -> ()) -> NFData a
rnf :: GenDelegs crypto -> ()
$crnf :: forall crypto. GenDelegs crypto -> ()
NFData, (forall x. GenDelegs crypto -> Rep (GenDelegs crypto) x)
-> (forall x. Rep (GenDelegs crypto) x -> GenDelegs crypto)
-> Generic (GenDelegs crypto)
forall x. Rep (GenDelegs crypto) x -> GenDelegs crypto
forall x. GenDelegs crypto -> Rep (GenDelegs crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (GenDelegs crypto) x -> GenDelegs crypto
forall crypto x. GenDelegs crypto -> Rep (GenDelegs crypto) x
$cto :: forall crypto x. Rep (GenDelegs crypto) x -> GenDelegs crypto
$cfrom :: forall crypto x. GenDelegs crypto -> Rep (GenDelegs crypto) x
Generic)
  deriving (Int -> GenDelegs crypto -> ShowS
[GenDelegs crypto] -> ShowS
GenDelegs crypto -> String
(Int -> GenDelegs crypto -> ShowS)
-> (GenDelegs crypto -> String)
-> ([GenDelegs crypto] -> ShowS)
-> Show (GenDelegs crypto)
forall crypto. Int -> GenDelegs crypto -> ShowS
forall crypto. [GenDelegs crypto] -> ShowS
forall crypto. GenDelegs crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenDelegs crypto] -> ShowS
$cshowList :: forall crypto. [GenDelegs crypto] -> ShowS
show :: GenDelegs crypto -> String
$cshow :: forall crypto. GenDelegs crypto -> String
showsPrec :: Int -> GenDelegs crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> GenDelegs crypto -> ShowS
Show) via Quiet (GenDelegs crypto)

deriving instance
  (Crypto crypto) =>
  ToCBOR (GenDelegs crypto)

newtype GKeys crypto = GKeys {GKeys crypto -> Set (VKey 'Genesis crypto)
unGKeys :: Set (VKey 'Genesis crypto)}
  deriving (GKeys crypto -> GKeys crypto -> Bool
(GKeys crypto -> GKeys crypto -> Bool)
-> (GKeys crypto -> GKeys crypto -> Bool) -> Eq (GKeys crypto)
forall crypto.
Crypto crypto =>
GKeys crypto -> GKeys crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GKeys crypto -> GKeys crypto -> Bool
$c/= :: forall crypto.
Crypto crypto =>
GKeys crypto -> GKeys crypto -> Bool
== :: GKeys crypto -> GKeys crypto -> Bool
$c== :: forall crypto.
Crypto crypto =>
GKeys crypto -> GKeys crypto -> Bool
Eq, Context -> GKeys crypto -> IO (Maybe ThunkInfo)
Proxy (GKeys crypto) -> String
(Context -> GKeys crypto -> IO (Maybe ThunkInfo))
-> (Context -> GKeys crypto -> IO (Maybe ThunkInfo))
-> (Proxy (GKeys crypto) -> String)
-> NoThunks (GKeys crypto)
forall crypto.
Crypto crypto =>
Context -> GKeys crypto -> IO (Maybe ThunkInfo)
forall crypto. Crypto crypto => Proxy (GKeys crypto) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (GKeys crypto) -> String
$cshowTypeOf :: forall crypto. Crypto crypto => Proxy (GKeys crypto) -> String
wNoThunks :: Context -> GKeys crypto -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall crypto.
Crypto crypto =>
Context -> GKeys crypto -> IO (Maybe ThunkInfo)
noThunks :: Context -> GKeys crypto -> IO (Maybe ThunkInfo)
$cnoThunks :: forall crypto.
Crypto crypto =>
Context -> GKeys crypto -> IO (Maybe ThunkInfo)
NoThunks, (forall x. GKeys crypto -> Rep (GKeys crypto) x)
-> (forall x. Rep (GKeys crypto) x -> GKeys crypto)
-> Generic (GKeys crypto)
forall x. Rep (GKeys crypto) x -> GKeys crypto
forall x. GKeys crypto -> Rep (GKeys crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (GKeys crypto) x -> GKeys crypto
forall crypto x. GKeys crypto -> Rep (GKeys crypto) x
$cto :: forall crypto x. Rep (GKeys crypto) x -> GKeys crypto
$cfrom :: forall crypto x. GKeys crypto -> Rep (GKeys crypto) x
Generic)
  deriving (Int -> GKeys crypto -> ShowS
[GKeys crypto] -> ShowS
GKeys crypto -> String
(Int -> GKeys crypto -> ShowS)
-> (GKeys crypto -> String)
-> ([GKeys crypto] -> ShowS)
-> Show (GKeys crypto)
forall crypto. Crypto crypto => Int -> GKeys crypto -> ShowS
forall crypto. Crypto crypto => [GKeys crypto] -> ShowS
forall crypto. Crypto crypto => GKeys crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GKeys crypto] -> ShowS
$cshowList :: forall crypto. Crypto crypto => [GKeys crypto] -> ShowS
show :: GKeys crypto -> String
$cshow :: forall crypto. Crypto crypto => GKeys crypto -> String
showsPrec :: Int -> GKeys crypto -> ShowS
$cshowsPrec :: forall crypto. Crypto crypto => Int -> GKeys crypto -> ShowS
Show) via Quiet (GKeys crypto)

--------------------------------------------------------------------------------
-- crypto-parametrised types
--
-- Within `cardano-ledger`, we parametrise everything on our `crypto` type
-- "package". However, in `cardano-crypto-class`, things are parametrised on the
-- original algorithm. In order to make using types from that module easier, we
-- provide some type aliases which unwrap the crypto parameters.
--------------------------------------------------------------------------------

type Hash c = Hash.Hash (HASH c)

type SignedDSIGN c = DSIGN.SignedDSIGN (DSIGN c)

type SignKeyDSIGN c = DSIGN.SignKeyDSIGN (DSIGN c)

type SignedKES c = KES.SignedKES (KES c)

type SignKeyKES c = KES.SignKeyKES (KES c)

type VerKeyKES c = KES.VerKeyKES (KES c)

type CertifiedVRF c = VRF.CertifiedVRF (VRF c)

type SignKeyVRF c = VRF.SignKeyVRF (VRF c)

type VerKeyVRF c = VRF.VerKeyVRF (VRF c)