{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneKindSignatures #-}
module Cardano.Crypto.Signing.Redeem.SigningKey (
RedeemSigningKey (..),
redeemToVerification,
)
where
import Cardano.Crypto.Signing.Redeem.VerificationKey (
RedeemVerificationKey (..),
redeemVKB64F,
)
import Cardano.Ledger.Binary (
DecCBOR,
EncCBOR,
FromCBOR (..),
ToCBOR (..),
fromByronCBOR,
toByronCBOR,
)
import Cardano.Prelude
import qualified Crypto.PubKey.Ed25519 as Ed25519
import Formatting (bprint)
import qualified Formatting.Buildable as B
import NoThunks.Class (InspectHeap (..), NoThunks (..))
type RedeemSigningKey :: Type
newtype RedeemSigningKey
= RedeemSigningKey Ed25519.SecretKey
deriving (RedeemSigningKey -> RedeemSigningKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RedeemSigningKey -> RedeemSigningKey -> Bool
$c/= :: RedeemSigningKey -> RedeemSigningKey -> Bool
== :: RedeemSigningKey -> RedeemSigningKey -> Bool
$c== :: RedeemSigningKey -> RedeemSigningKey -> Bool
Eq, Int -> RedeemSigningKey -> ShowS
[RedeemSigningKey] -> ShowS
RedeemSigningKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RedeemSigningKey] -> ShowS
$cshowList :: [RedeemSigningKey] -> ShowS
show :: RedeemSigningKey -> String
$cshow :: RedeemSigningKey -> String
showsPrec :: Int -> RedeemSigningKey -> ShowS
$cshowsPrec :: Int -> RedeemSigningKey -> ShowS
Show, forall x. Rep RedeemSigningKey x -> RedeemSigningKey
forall x. RedeemSigningKey -> Rep RedeemSigningKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RedeemSigningKey x -> RedeemSigningKey
$cfrom :: forall x. RedeemSigningKey -> Rep RedeemSigningKey x
Generic, RedeemSigningKey -> ()
forall a. (a -> ()) -> NFData a
rnf :: RedeemSigningKey -> ()
$crnf :: RedeemSigningKey -> ()
NFData, Typeable RedeemSigningKey
Proxy RedeemSigningKey -> Text
forall s. Decoder s RedeemSigningKey
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy RedeemSigningKey -> Decoder s ()
label :: Proxy RedeemSigningKey -> Text
$clabel :: Proxy RedeemSigningKey -> Text
dropCBOR :: forall s. Proxy RedeemSigningKey -> Decoder s ()
$cdropCBOR :: forall s. Proxy RedeemSigningKey -> Decoder s ()
decCBOR :: forall s. Decoder s RedeemSigningKey
$cdecCBOR :: forall s. Decoder s RedeemSigningKey
DecCBOR, Typeable RedeemSigningKey
RedeemSigningKey -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [RedeemSigningKey] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy RedeemSigningKey -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [RedeemSigningKey] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [RedeemSigningKey] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy RedeemSigningKey -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy RedeemSigningKey -> Size
encCBOR :: RedeemSigningKey -> Encoding
$cencCBOR :: RedeemSigningKey -> Encoding
EncCBOR)
deriving (Context -> RedeemSigningKey -> IO (Maybe ThunkInfo)
Proxy RedeemSigningKey -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy RedeemSigningKey -> String
$cshowTypeOf :: Proxy RedeemSigningKey -> String
wNoThunks :: Context -> RedeemSigningKey -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> RedeemSigningKey -> IO (Maybe ThunkInfo)
noThunks :: Context -> RedeemSigningKey -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> RedeemSigningKey -> IO (Maybe ThunkInfo)
NoThunks) via InspectHeap RedeemSigningKey
instance ToCBOR RedeemSigningKey where
toCBOR :: RedeemSigningKey -> Encoding
toCBOR = forall a. EncCBOR a => a -> Encoding
toByronCBOR
instance FromCBOR RedeemSigningKey where
fromCBOR :: forall s. Decoder s RedeemSigningKey
fromCBOR = forall a s. DecCBOR a => Decoder s a
fromByronCBOR
instance B.Buildable RedeemSigningKey where
build :: RedeemSigningKey -> Builder
build = forall a. Format Builder a -> a
bprint (Format
(RedeemVerificationKey -> Builder)
(RedeemVerificationKey -> Builder)
"redeem_sec_of_vk:" forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall r. Format r (RedeemVerificationKey -> r)
redeemVKB64F) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. RedeemSigningKey -> RedeemVerificationKey
redeemToVerification
redeemToVerification :: RedeemSigningKey -> RedeemVerificationKey
redeemToVerification :: RedeemSigningKey -> RedeemVerificationKey
redeemToVerification (RedeemSigningKey SecretKey
k) = PublicKey -> RedeemVerificationKey
RedeemVerificationKey (SecretKey -> PublicKey
Ed25519.toPublic SecretKey
k)