{-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} module Cardano.CLI.EraBased.Governance.Committee.Run ( runGovernanceCommitteeCmds , runGovernanceCommitteeKeyGenCold , runGovernanceCommitteeKeyGenHot ) where import Cardano.Api import Cardano.Api.Experimental (obtainCommonConstraints) import Cardano.CLI.Compatible.Exception import Cardano.CLI.EraBased.Governance.Committee.Command import Cardano.CLI.EraBased.Governance.Committee.Command qualified as Cmd import Cardano.CLI.EraIndependent.Hash.Internal.Common (carryHashChecks) import Cardano.CLI.EraIndependent.Key.Run qualified as Key import Cardano.CLI.Orphan () import Cardano.CLI.Read (readVerificationKeySource) import Cardano.CLI.Type.Common (PotentiallyCheckedAnchor (..)) import Cardano.CLI.Type.Key.VerificationKey import Control.Monad (void) import Data.ByteString (ByteString) import Data.ByteString.Char8 qualified as BS import Data.Function runGovernanceCommitteeCmds :: () => GovernanceCommitteeCmds era -> CIO e () runGovernanceCommitteeCmds :: forall era e. GovernanceCommitteeCmds era -> CIO e () runGovernanceCommitteeCmds = \case GovernanceCommitteeKeyGenColdCmd GovernanceCommitteeKeyGenColdCmdArgs era cmd -> RIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) -> RIO e () forall (f :: * -> *) a. Functor f => f a -> f () void (RIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) -> RIO e ()) -> RIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) -> RIO e () forall a b. (a -> b) -> a -> b $ GovernanceCommitteeKeyGenColdCmdArgs era -> CIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) forall era e. GovernanceCommitteeKeyGenColdCmdArgs era -> CIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) runGovernanceCommitteeKeyGenCold GovernanceCommitteeKeyGenColdCmdArgs era cmd GovernanceCommitteeKeyGenHotCmd GovernanceCommitteeKeyGenHotCmdArgs era cmd -> RIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) -> RIO e () forall (f :: * -> *) a. Functor f => f a -> f () void (RIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) -> RIO e ()) -> RIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) -> RIO e () forall a b. (a -> b) -> a -> b $ GovernanceCommitteeKeyGenHotCmdArgs era -> CIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) forall era e. GovernanceCommitteeKeyGenHotCmdArgs era -> CIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) runGovernanceCommitteeKeyGenHot GovernanceCommitteeKeyGenHotCmdArgs era cmd GovernanceCommitteeKeyHashCmd GovernanceCommitteeKeyHashCmdArgs era cmd -> GovernanceCommitteeKeyHashCmdArgs era -> CIO e () forall era e. GovernanceCommitteeKeyHashCmdArgs era -> CIO e () runGovernanceCommitteeKeyHash GovernanceCommitteeKeyHashCmdArgs era cmd GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmd GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era cmd -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> CIO e () forall era e. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> CIO e () runGovernanceCommitteeCreateHotKeyAuthorizationCertificate GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era cmd GovernanceCommitteeCreateColdKeyResignationCertificateCmd GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era cmd -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> CIO e () forall era e. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> CIO e () runGovernanceCommitteeColdKeyResignationCertificate GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era cmd runGovernanceCommitteeKeyGenCold :: Cmd.GovernanceCommitteeKeyGenColdCmdArgs era -> CIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) runGovernanceCommitteeKeyGenCold :: forall era e. GovernanceCommitteeKeyGenColdCmdArgs era -> CIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) runGovernanceCommitteeKeyGenCold Cmd.GovernanceCommitteeKeyGenColdCmdArgs { vkeyOutFile :: forall era. GovernanceCommitteeKeyGenColdCmdArgs era -> File (VerificationKey ()) 'Out Cmd.vkeyOutFile = File (VerificationKey ()) 'Out vkeyPath , skeyOutFile :: forall era. GovernanceCommitteeKeyGenColdCmdArgs era -> File (SigningKey ()) 'Out Cmd.skeyOutFile = File (SigningKey ()) 'Out skeyPath } = do SigningKey CommitteeColdKey skey <- AsType CommitteeColdKey -> RIO e (SigningKey CommitteeColdKey) forall (m :: * -> *) keyrole. (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole) generateSigningKey AsType CommitteeColdKey AsCommitteeColdKey let vkey :: VerificationKey CommitteeColdKey vkey = SigningKey CommitteeColdKey -> VerificationKey CommitteeColdKey forall keyrole. (Key keyrole, HasTypeProxy keyrole) => SigningKey keyrole -> VerificationKey keyrole getVerificationKey SigningKey CommitteeColdKey skey forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli @(FileError ()) (IO (Either (FileError ()) ()) -> RIO e ()) -> IO (Either (FileError ()) ()) -> RIO e () forall a b. (a -> b) -> a -> b $ File (SigningKey ()) 'Out -> ByteString -> IO (Either (FileError ()) ()) forall (m :: * -> *) content e. MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) writeLazyByteStringFile File (SigningKey ()) 'Out skeyPath (Maybe TextEnvelopeDescr -> SigningKey CommitteeColdKey -> ByteString forall a. HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString textEnvelopeToJSON (TextEnvelopeDescr -> Maybe TextEnvelopeDescr forall a. a -> Maybe a Just TextEnvelopeDescr Key.ccColdSkeyDesc) SigningKey CommitteeColdKey skey) forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli @(FileError ()) (IO (Either (FileError ()) ()) -> RIO e ()) -> IO (Either (FileError ()) ()) -> RIO e () forall a b. (a -> b) -> a -> b $ File (VerificationKey ()) 'Out -> ByteString -> IO (Either (FileError ()) ()) forall (m :: * -> *) content e. MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) writeLazyByteStringFile File (VerificationKey ()) 'Out vkeyPath (Maybe TextEnvelopeDescr -> VerificationKey CommitteeColdKey -> ByteString forall a. HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString textEnvelopeToJSON (TextEnvelopeDescr -> Maybe TextEnvelopeDescr forall a. a -> Maybe a Just TextEnvelopeDescr Key.ccColdVkeyDesc) VerificationKey CommitteeColdKey vkey) (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) -> RIO e (VerificationKey CommitteeColdKey, SigningKey CommitteeColdKey) forall a. a -> RIO e a forall (m :: * -> *) a. Monad m => a -> m a return (VerificationKey CommitteeColdKey vkey, SigningKey CommitteeColdKey skey) runGovernanceCommitteeKeyGenHot :: Cmd.GovernanceCommitteeKeyGenHotCmdArgs era -> CIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) runGovernanceCommitteeKeyGenHot :: forall era e. GovernanceCommitteeKeyGenHotCmdArgs era -> CIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) runGovernanceCommitteeKeyGenHot Cmd.GovernanceCommitteeKeyGenHotCmdArgs { era :: forall era. GovernanceCommitteeKeyGenHotCmdArgs era -> Era era Cmd.era = Era era _eon , vkeyOutFile :: forall era. GovernanceCommitteeKeyGenHotCmdArgs era -> File (VerificationKey ()) 'Out Cmd.vkeyOutFile = File (VerificationKey ()) 'Out vkeyPath , skeyOutFile :: forall era. GovernanceCommitteeKeyGenHotCmdArgs era -> File (SigningKey ()) 'Out Cmd.skeyOutFile = File (SigningKey ()) 'Out skeyPath } = do SigningKey CommitteeHotKey skey <- AsType CommitteeHotKey -> RIO e (SigningKey CommitteeHotKey) forall (m :: * -> *) keyrole. (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole) generateSigningKey AsType CommitteeHotKey AsCommitteeHotKey let vkey :: VerificationKey CommitteeHotKey vkey = SigningKey CommitteeHotKey -> VerificationKey CommitteeHotKey forall keyrole. (Key keyrole, HasTypeProxy keyrole) => SigningKey keyrole -> VerificationKey keyrole getVerificationKey SigningKey CommitteeHotKey skey forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli @(FileError ()) (IO (Either (FileError ()) ()) -> RIO e ()) -> IO (Either (FileError ()) ()) -> RIO e () forall a b. (a -> b) -> a -> b $ File (SigningKey ()) 'Out -> ByteString -> IO (Either (FileError ()) ()) forall (m :: * -> *) content e. MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) writeLazyByteStringFile File (SigningKey ()) 'Out skeyPath (ByteString -> IO (Either (FileError ()) ())) -> ByteString -> IO (Either (FileError ()) ()) forall a b. (a -> b) -> a -> b $ Maybe TextEnvelopeDescr -> SigningKey CommitteeHotKey -> ByteString forall a. HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString textEnvelopeToJSON (TextEnvelopeDescr -> Maybe TextEnvelopeDescr forall a. a -> Maybe a Just TextEnvelopeDescr Key.ccHotSkeyDesc) SigningKey CommitteeHotKey skey forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli @(FileError ()) (IO (Either (FileError ()) ()) -> RIO e ()) -> IO (Either (FileError ()) ()) -> RIO e () forall a b. (a -> b) -> a -> b $ File (VerificationKey ()) 'Out -> ByteString -> IO (Either (FileError ()) ()) forall (m :: * -> *) content e. MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) writeLazyByteStringFile File (VerificationKey ()) 'Out vkeyPath (ByteString -> IO (Either (FileError ()) ())) -> ByteString -> IO (Either (FileError ()) ()) forall a b. (a -> b) -> a -> b $ Maybe TextEnvelopeDescr -> VerificationKey CommitteeHotKey -> ByteString forall a. HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString textEnvelopeToJSON (TextEnvelopeDescr -> Maybe TextEnvelopeDescr forall a. a -> Maybe a Just TextEnvelopeDescr Key.ccHotVkeyDesc) VerificationKey CommitteeHotKey vkey (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) -> RIO e (VerificationKey CommitteeHotKey, SigningKey CommitteeHotKey) forall a. a -> RIO e a forall (m :: * -> *) a. Monad m => a -> m a return (VerificationKey CommitteeHotKey vkey, SigningKey CommitteeHotKey skey) data SomeCommitteeKey = ACommitteeHotKey (VerificationKey CommitteeHotKey) | ACommitteeHotExtendedKey (VerificationKey CommitteeHotExtendedKey) | ACommitteeColdKey (VerificationKey CommitteeColdKey) | ACommitteeColdExtendedKey (VerificationKey CommitteeColdExtendedKey) runGovernanceCommitteeKeyHash :: () => Cmd.GovernanceCommitteeKeyHashCmdArgs era -> CIO e () runGovernanceCommitteeKeyHash :: forall era e. GovernanceCommitteeKeyHashCmdArgs era -> CIO e () runGovernanceCommitteeKeyHash Cmd.GovernanceCommitteeKeyHashCmdArgs { AnyVerificationKeySource vkeySource :: AnyVerificationKeySource vkeySource :: forall era. GovernanceCommitteeKeyHashCmdArgs era -> AnyVerificationKeySource Cmd.vkeySource } = do SomeCommitteeKey vkey <- case AnyVerificationKeySource vkeySource of AnyVerificationKeySourceOfText AnyVerificationKeyText vkText -> do let asTypes :: [FromSomeType SerialiseAsBech32 SomeCommitteeKey] asTypes = [ AsType (VerificationKey CommitteeHotKey) -> (VerificationKey CommitteeHotKey -> SomeCommitteeKey) -> FromSomeType SerialiseAsBech32 SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeHotKey -> AsType (VerificationKey CommitteeHotKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeHotKey AsCommitteeHotKey) VerificationKey CommitteeHotKey -> SomeCommitteeKey ACommitteeHotKey , AsType (VerificationKey CommitteeHotExtendedKey) -> (VerificationKey CommitteeHotExtendedKey -> SomeCommitteeKey) -> FromSomeType SerialiseAsBech32 SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeHotExtendedKey -> AsType (VerificationKey CommitteeHotExtendedKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeHotExtendedKey AsCommitteeHotExtendedKey) VerificationKey CommitteeHotExtendedKey -> SomeCommitteeKey ACommitteeHotExtendedKey , AsType (VerificationKey CommitteeColdKey) -> (VerificationKey CommitteeColdKey -> SomeCommitteeKey) -> FromSomeType SerialiseAsBech32 SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeColdKey -> AsType (VerificationKey CommitteeColdKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeColdKey AsCommitteeColdKey) VerificationKey CommitteeColdKey -> SomeCommitteeKey ACommitteeColdKey , AsType (VerificationKey CommitteeColdExtendedKey) -> (VerificationKey CommitteeColdExtendedKey -> SomeCommitteeKey) -> FromSomeType SerialiseAsBech32 SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeColdExtendedKey -> AsType (VerificationKey CommitteeColdExtendedKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeColdExtendedKey AsCommitteeColdExtendedKey) VerificationKey CommitteeColdExtendedKey -> SomeCommitteeKey ACommitteeColdExtendedKey ] Either Bech32DecodeError SomeCommitteeKey -> RIO e SomeCommitteeKey forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => Either e a -> m a fromEitherCli (Either Bech32DecodeError SomeCommitteeKey -> RIO e SomeCommitteeKey) -> (Text -> Either Bech32DecodeError SomeCommitteeKey) -> Text -> RIO e SomeCommitteeKey forall b c a. (b -> c) -> (a -> b) -> a -> c . [FromSomeType SerialiseAsBech32 SomeCommitteeKey] -> Text -> Either Bech32DecodeError SomeCommitteeKey forall b. [FromSomeType SerialiseAsBech32 b] -> Text -> Either Bech32DecodeError b deserialiseAnyOfFromBech32 [FromSomeType SerialiseAsBech32 SomeCommitteeKey] asTypes (Text -> RIO e SomeCommitteeKey) -> Text -> RIO e SomeCommitteeKey forall a b. (a -> b) -> a -> b $ AnyVerificationKeyText -> Text unAnyVerificationKeyText AnyVerificationKeyText vkText AnyVerificationKeySourceOfFile File (VerificationKey ()) 'In vkeyPath -> do let asTypes :: [FromSomeType HasTextEnvelope SomeCommitteeKey] asTypes = [ AsType (VerificationKey CommitteeHotKey) -> (VerificationKey CommitteeHotKey -> SomeCommitteeKey) -> FromSomeType HasTextEnvelope SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeHotKey -> AsType (VerificationKey CommitteeHotKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeHotKey AsCommitteeHotKey) VerificationKey CommitteeHotKey -> SomeCommitteeKey ACommitteeHotKey , AsType (VerificationKey CommitteeHotExtendedKey) -> (VerificationKey CommitteeHotExtendedKey -> SomeCommitteeKey) -> FromSomeType HasTextEnvelope SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeHotExtendedKey -> AsType (VerificationKey CommitteeHotExtendedKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeHotExtendedKey AsCommitteeHotExtendedKey) VerificationKey CommitteeHotExtendedKey -> SomeCommitteeKey ACommitteeHotExtendedKey , AsType (VerificationKey CommitteeColdKey) -> (VerificationKey CommitteeColdKey -> SomeCommitteeKey) -> FromSomeType HasTextEnvelope SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeColdKey -> AsType (VerificationKey CommitteeColdKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeColdKey AsCommitteeColdKey) VerificationKey CommitteeColdKey -> SomeCommitteeKey ACommitteeColdKey , AsType (VerificationKey CommitteeColdExtendedKey) -> (VerificationKey CommitteeColdExtendedKey -> SomeCommitteeKey) -> FromSomeType HasTextEnvelope SomeCommitteeKey forall (c :: * -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b FromSomeType (AsType CommitteeColdExtendedKey -> AsType (VerificationKey CommitteeColdExtendedKey) forall a. AsType a -> AsType (VerificationKey a) AsVerificationKey AsType CommitteeColdExtendedKey AsCommitteeColdExtendedKey) VerificationKey CommitteeColdExtendedKey -> SomeCommitteeKey ACommitteeColdExtendedKey ] IO (Either (FileError TextEnvelopeError) SomeCommitteeKey) -> RIO e SomeCommitteeKey forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli (IO (Either (FileError TextEnvelopeError) SomeCommitteeKey) -> RIO e SomeCommitteeKey) -> IO (Either (FileError TextEnvelopeError) SomeCommitteeKey) -> RIO e SomeCommitteeKey forall a b. (a -> b) -> a -> b $ [FromSomeType HasTextEnvelope SomeCommitteeKey] -> File (VerificationKey ()) 'In -> IO (Either (FileError TextEnvelopeError) SomeCommitteeKey) forall b content. [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError TextEnvelopeError) b) readFileTextEnvelopeAnyOf [FromSomeType HasTextEnvelope SomeCommitteeKey] asTypes File (VerificationKey ()) 'In vkeyPath IO () -> RIO e () forall a. IO a -> RIO e a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> RIO e ()) -> IO () -> RIO e () forall a b. (a -> b) -> a -> b $ ByteString -> IO () BS.putStrLn (SomeCommitteeKey -> ByteString renderKeyHash SomeCommitteeKey vkey) where renderKeyHash :: SomeCommitteeKey -> ByteString renderKeyHash :: SomeCommitteeKey -> ByteString renderKeyHash = \case ACommitteeHotKey VerificationKey CommitteeHotKey vk -> VerificationKey CommitteeHotKey -> ByteString forall keyrole. Key keyrole => VerificationKey keyrole -> ByteString renderVerificationKeyHash VerificationKey CommitteeHotKey vk ACommitteeHotExtendedKey VerificationKey CommitteeHotExtendedKey vk -> VerificationKey CommitteeHotExtendedKey -> ByteString forall keyrole. Key keyrole => VerificationKey keyrole -> ByteString renderVerificationKeyHash VerificationKey CommitteeHotExtendedKey vk ACommitteeColdKey VerificationKey CommitteeColdKey vk -> VerificationKey CommitteeColdKey -> ByteString forall keyrole. Key keyrole => VerificationKey keyrole -> ByteString renderVerificationKeyHash VerificationKey CommitteeColdKey vk ACommitteeColdExtendedKey VerificationKey CommitteeColdExtendedKey vk -> VerificationKey CommitteeColdExtendedKey -> ByteString forall keyrole. Key keyrole => VerificationKey keyrole -> ByteString renderVerificationKeyHash VerificationKey CommitteeColdExtendedKey vk renderVerificationKeyHash :: Key keyrole => VerificationKey keyrole -> ByteString renderVerificationKeyHash :: forall keyrole. Key keyrole => VerificationKey keyrole -> ByteString renderVerificationKeyHash = Hash keyrole -> ByteString forall a. SerialiseAsRawBytes a => a -> ByteString serialiseToRawBytesHex (Hash keyrole -> ByteString) -> (VerificationKey keyrole -> Hash keyrole) -> VerificationKey keyrole -> ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . VerificationKey keyrole -> Hash keyrole forall keyrole. Key keyrole => VerificationKey keyrole -> Hash keyrole verificationKeyHash runGovernanceCommitteeCreateHotKeyAuthorizationCertificate :: () => Cmd.GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> CIO e () runGovernanceCommitteeCreateHotKeyAuthorizationCertificate :: forall era e. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> CIO e () runGovernanceCommitteeCreateHotKeyAuthorizationCertificate Cmd.GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs { era :: forall era. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> Era era Cmd.era = Era era eon , VerificationKeySource CommitteeColdKey vkeyColdKeySource :: VerificationKeySource CommitteeColdKey vkeyColdKeySource :: forall era. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> VerificationKeySource CommitteeColdKey Cmd.vkeyColdKeySource , VerificationKeySource CommitteeHotKey vkeyHotKeySource :: VerificationKeySource CommitteeHotKey vkeyHotKeySource :: forall era. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> VerificationKeySource CommitteeHotKey Cmd.vkeyHotKeySource , outFile :: forall era. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> File () 'Out Cmd.outFile = File () 'Out oFp } = Era era -> (EraCommonConstraints era => RIO e ()) -> RIO e () forall era a. Era era -> (EraCommonConstraints era => a) -> a obtainCommonConstraints Era era eon ((EraCommonConstraints era => RIO e ()) -> RIO e ()) -> (EraCommonConstraints era => RIO e ()) -> RIO e () forall a b. (a -> b) -> a -> b $ do Credential 'HotCommitteeRole hotCred <- (Hash CommitteeHotKey -> KeyHash 'HotCommitteeRole) -> VerificationKeySource CommitteeHotKey -> CIO e (Credential 'HotCommitteeRole) forall keyrole (kr :: KeyRole) e. Key keyrole => (Hash keyrole -> KeyHash kr) -> VerificationKeySource keyrole -> CIO e (Credential kr) readVerificationKeySource Hash CommitteeHotKey -> KeyHash 'HotCommitteeRole unCommitteeHotKeyHash VerificationKeySource CommitteeHotKey vkeyHotKeySource Credential 'ColdCommitteeRole coldCred <- (Hash CommitteeColdKey -> KeyHash 'ColdCommitteeRole) -> VerificationKeySource CommitteeColdKey -> CIO e (Credential 'ColdCommitteeRole) forall keyrole (kr :: KeyRole) e. Key keyrole => (Hash keyrole -> KeyHash kr) -> VerificationKeySource keyrole -> CIO e (Credential kr) readVerificationKeySource Hash CommitteeColdKey -> KeyHash 'ColdCommitteeRole unCommitteeColdKeyHash VerificationKeySource CommitteeColdKey vkeyColdKeySource forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli @(FileError ()) (IO (Either (FileError ()) ()) -> RIO e ()) -> IO (Either (FileError ()) ()) -> RIO e () forall a b. (a -> b) -> a -> b $ CommitteeHotKeyAuthorizationRequirements era -> Certificate era forall era. Typeable era => CommitteeHotKeyAuthorizationRequirements era -> Certificate era makeCommitteeHotKeyAuthorizationCertificate (ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> CommitteeHotKeyAuthorizationRequirements era forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> CommitteeHotKeyAuthorizationRequirements era CommitteeHotKeyAuthorizationRequirements (Era era -> ConwayEraOnwards era forall era. Era era -> ConwayEraOnwards era forall a (f :: a -> *) (g :: a -> *) (era :: a). Convert f g => f era -> g era convert Era era eon) Credential 'ColdCommitteeRole coldCred Credential 'HotCommitteeRole hotCred) Certificate era -> (Certificate era -> ByteString) -> ByteString forall a b. a -> (a -> b) -> b & Maybe TextEnvelopeDescr -> Certificate era -> ByteString forall a. HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString textEnvelopeToJSON (TextEnvelopeDescr -> Maybe TextEnvelopeDescr forall a. a -> Maybe a Just TextEnvelopeDescr genKeyDelegCertDesc) ByteString -> (ByteString -> IO (Either (FileError ()) ())) -> IO (Either (FileError ()) ()) forall a b. a -> (a -> b) -> b & File () 'Out -> ByteString -> IO (Either (FileError ()) ()) forall (m :: * -> *) content e. MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) writeLazyByteStringFile File () 'Out oFp where genKeyDelegCertDesc :: TextEnvelopeDescr genKeyDelegCertDesc :: TextEnvelopeDescr genKeyDelegCertDesc = TextEnvelopeDescr "Constitutional Committee Hot Key Registration Certificate" runGovernanceCommitteeColdKeyResignationCertificate :: () => Cmd.GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> CIO e () runGovernanceCommitteeColdKeyResignationCertificate :: forall era e. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> CIO e () runGovernanceCommitteeColdKeyResignationCertificate Cmd.GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs { Era era era :: Era era era :: forall era. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> Era era Cmd.era , VerificationKeySource CommitteeColdKey vkeyColdKeySource :: VerificationKeySource CommitteeColdKey vkeyColdKeySource :: forall era. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> VerificationKeySource CommitteeColdKey Cmd.vkeyColdKeySource , Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) anchor :: Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) anchor :: forall era. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) Cmd.anchor , File () 'Out outFile :: File () 'Out outFile :: forall era. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> File () 'Out Cmd.outFile } = Era era -> (EraCommonConstraints era => RIO e ()) -> RIO e () forall era a. Era era -> (EraCommonConstraints era => a) -> a obtainCommonConstraints Era era era ((EraCommonConstraints era => RIO e ()) -> RIO e ()) -> (EraCommonConstraints era => RIO e ()) -> RIO e () forall a b. (a -> b) -> a -> b $ do Credential 'ColdCommitteeRole coldVKeyCred <- (Hash CommitteeColdKey -> KeyHash 'ColdCommitteeRole) -> VerificationKeySource CommitteeColdKey -> CIO e (Credential 'ColdCommitteeRole) forall keyrole (kr :: KeyRole) e. Key keyrole => (Hash keyrole -> KeyHash kr) -> VerificationKeySource keyrole -> CIO e (Credential kr) readVerificationKeySource Hash CommitteeColdKey -> KeyHash 'ColdCommitteeRole unCommitteeColdKeyHash VerificationKeySource CommitteeColdKey vkeyColdKeySource (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor -> RIO e ()) -> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) -> RIO e () forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ (ExceptT HashCheckError IO () -> RIO e () forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => ExceptT e IO a -> m a fromExceptTCli (ExceptT HashCheckError IO () -> RIO e ()) -> (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor -> ExceptT HashCheckError IO ()) -> PotentiallyCheckedAnchor ResignationMetadataUrl Anchor -> RIO e () forall b c a. (b -> c) -> (a -> b) -> a -> c . PotentiallyCheckedAnchor ResignationMetadataUrl Anchor -> ExceptT HashCheckError IO () forall anchorType. PotentiallyCheckedAnchor anchorType Anchor -> ExceptT HashCheckError IO () carryHashChecks) Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) anchor forall e (m :: * -> *) a. (HasCallStack, MonadIO m, Show e, Typeable e, Error e) => IO (Either e a) -> m a fromEitherIOCli @(FileError ()) (IO (Either (FileError ()) ()) -> RIO e ()) -> IO (Either (FileError ()) ()) -> RIO e () forall a b. (a -> b) -> a -> b $ CommitteeColdkeyResignationRequirements era -> Certificate era forall era. Typeable era => CommitteeColdkeyResignationRequirements era -> Certificate era makeCommitteeColdkeyResignationCertificate (ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Maybe Anchor -> CommitteeColdkeyResignationRequirements era forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Maybe Anchor -> CommitteeColdkeyResignationRequirements era CommitteeColdkeyResignationRequirements (Era era -> ConwayEraOnwards era forall era. Era era -> ConwayEraOnwards era forall a (f :: a -> *) (g :: a -> *) (era :: a). Convert f g => f era -> g era convert Era era era) Credential 'ColdCommitteeRole coldVKeyCred (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor -> Anchor forall anchorType anchor. PotentiallyCheckedAnchor anchorType anchor -> anchor pcaAnchor (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor -> Anchor) -> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) -> Maybe Anchor forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl Anchor) anchor)) Certificate era -> (Certificate era -> ByteString) -> ByteString forall a b. a -> (a -> b) -> b & Maybe TextEnvelopeDescr -> Certificate era -> ByteString forall a. HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString textEnvelopeToJSON (TextEnvelopeDescr -> Maybe TextEnvelopeDescr forall a. a -> Maybe a Just TextEnvelopeDescr genKeyDelegCertDesc) ByteString -> (ByteString -> IO (Either (FileError ()) ())) -> IO (Either (FileError ()) ()) forall a b. a -> (a -> b) -> b & File () 'Out -> ByteString -> IO (Either (FileError ()) ()) forall (m :: * -> *) content e. MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) writeLazyByteStringFile File () 'Out outFile where genKeyDelegCertDesc :: TextEnvelopeDescr genKeyDelegCertDesc :: TextEnvelopeDescr genKeyDelegCertDesc = TextEnvelopeDescr "Constitutional Committee Cold Key Resignation Certificate"