{-# LANGUAGE GADTs #-}
module Bcc.CLI.Cole.Run
( ColeClientCmdError
, renderColeClientCmdError
, runColeClientCommand
) where
import Bcc.Prelude
import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither, left)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Text as Text
import qualified Data.Text.Lazy.Builder as Builder
import qualified Data.Text.Lazy.IO as TL
import qualified Formatting as F
import qualified Bcc.Chain.Genesis as Genesis
import qualified Bcc.Crypto.Hashing as Crypto
import qualified Bcc.Crypto.Signing as Crypto
import Bcc.Api hiding (UpdateProposal, GenesisParameters)
import Bcc.Api.Cole (SomeColeSigningKey (..), Tx (..), VerificationKey (..))
import Shardagnostic.Consensus.Cole.Ledger (ColeBlock)
import Shardagnostic.Consensus.Ledger.SupportsMempool (ApplyTxErr)
import Bcc.CLI.Cole.Commands
import Bcc.CLI.Cole.Delegation
import Bcc.CLI.Cole.Genesis
import Bcc.CLI.Cole.Key
import Bcc.CLI.Cole.Query
import Bcc.CLI.Cole.Tx
import Bcc.CLI.Cole.UpdateProposal
import Bcc.CLI.Cole.Vote
import Bcc.CLI.Helpers
import Bcc.CLI.Sophie.Commands (ColeKeyFormat (..))
import Bcc.CLI.Types
data ColeClientCmdError
= ColeCmdDelegationError !ColeDelegationError
| ColeCmdGenesisError !ColeGenesisError
| ColeCmdHelpersError !HelpersError
| ColeCmdKeyFailure !ColeKeyFailure
| ColeCmdQueryError !ColeQueryError
| ColeCmdTxError !ColeTxError
| ColeCmdTxSubmitError !(ApplyTxErr ColeBlock)
| ColeCmdUpdateProposalError !ColeUpdateProposalError
| ColeCmdVoteError !ColeVoteError
deriving Int -> ColeClientCmdError -> ShowS
[ColeClientCmdError] -> ShowS
ColeClientCmdError -> String
(Int -> ColeClientCmdError -> ShowS)
-> (ColeClientCmdError -> String)
-> ([ColeClientCmdError] -> ShowS)
-> Show ColeClientCmdError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColeClientCmdError] -> ShowS
$cshowList :: [ColeClientCmdError] -> ShowS
show :: ColeClientCmdError -> String
$cshow :: ColeClientCmdError -> String
showsPrec :: Int -> ColeClientCmdError -> ShowS
$cshowsPrec :: Int -> ColeClientCmdError -> ShowS
Show
renderColeClientCmdError :: ColeClientCmdError -> Text
renderColeClientCmdError :: ColeClientCmdError -> Text
renderColeClientCmdError ColeClientCmdError
err =
case ColeClientCmdError
err of
ColeCmdDelegationError ColeDelegationError
e -> ColeDelegationError -> Text
renderColeDelegationError ColeDelegationError
e
ColeCmdGenesisError ColeGenesisError
e -> ColeGenesisError -> Text
renderColeGenesisError ColeGenesisError
e
ColeCmdHelpersError HelpersError
e -> HelpersError -> Text
renderHelpersError HelpersError
e
ColeCmdKeyFailure ColeKeyFailure
e -> ColeKeyFailure -> Text
renderColeKeyFailure ColeKeyFailure
e
ColeCmdQueryError ColeQueryError
e -> ColeQueryError -> Text
renderColeQueryError ColeQueryError
e
ColeCmdTxError ColeTxError
e -> ColeTxError -> Text
renderColeTxError ColeTxError
e
ColeCmdTxSubmitError ApplyTxErr ColeBlock
e ->
Text
"Error while submitting Cole tx: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (ApplyMempoolPayloadErr -> String
forall a b. (Show a, ConvertText String b) => a -> b
show ApplyMempoolPayloadErr
ApplyTxErr ColeBlock
e)
ColeCmdUpdateProposalError ColeUpdateProposalError
e -> ColeUpdateProposalError -> Text
renderColeUpdateProposalError ColeUpdateProposalError
e
ColeCmdVoteError ColeVoteError
e -> ColeVoteError -> Text
renderColeVoteError ColeVoteError
e
runColeClientCommand :: ColeCommand -> ExceptT ColeClientCmdError IO ()
runColeClientCommand :: ColeCommand -> ExceptT ColeClientCmdError IO ()
runColeClientCommand ColeCommand
c =
case ColeCommand
c of
NodeCmd NodeCmd
bc -> NodeCmd -> ExceptT ColeClientCmdError IO ()
runNodeCmd NodeCmd
bc
Genesis NewDirectory
outDir GenesisParameters
params -> NewDirectory
-> GenesisParameters -> ExceptT ColeClientCmdError IO ()
runGenesisCommand NewDirectory
outDir GenesisParameters
params
GetLocalNodeTip NetworkId
network -> (ColeQueryError -> ColeClientCmdError)
-> ExceptT ColeQueryError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeQueryError -> ColeClientCmdError
ColeCmdQueryError (ExceptT ColeQueryError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeQueryError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ NetworkId -> ExceptT ColeQueryError IO ()
runGetLocalNodeTip NetworkId
network
ValidateCBOR CBORObject
cborObject String
fp -> CBORObject -> String -> ExceptT ColeClientCmdError IO ()
runValidateCBOR CBORObject
cborObject String
fp
PrettyPrintCBOR String
fp -> String -> ExceptT ColeClientCmdError IO ()
runPrettyPrintCBOR String
fp
PrettySigningKeyPublic ColeKeyFormat
bKeyFormat SigningKeyFile
skF -> ColeKeyFormat -> SigningKeyFile -> ExceptT ColeClientCmdError IO ()
runPrettySigningKeyPublic ColeKeyFormat
bKeyFormat SigningKeyFile
skF
MigrateDelegateKeyFrom SigningKeyFile
oldKey NewSigningKeyFile
nskf ->
SigningKeyFile
-> NewSigningKeyFile -> ExceptT ColeClientCmdError IO ()
runMigrateDelegateKeyFrom SigningKeyFile
oldKey NewSigningKeyFile
nskf
PrintGenesisHash GenesisFile
genFp -> GenesisFile -> ExceptT ColeClientCmdError IO ()
runPrintGenesisHash GenesisFile
genFp
PrintSigningKeyAddress ColeKeyFormat
bKeyFormat NetworkId
networkid SigningKeyFile
skF -> ColeKeyFormat
-> NetworkId -> SigningKeyFile -> ExceptT ColeClientCmdError IO ()
runPrintSigningKeyAddress ColeKeyFormat
bKeyFormat NetworkId
networkid SigningKeyFile
skF
Keygen NewSigningKeyFile
nskf -> NewSigningKeyFile -> ExceptT ColeClientCmdError IO ()
runKeygen NewSigningKeyFile
nskf
ToVerification ColeKeyFormat
bKeyFormat SigningKeyFile
skFp NewVerificationKeyFile
nvkFp -> ColeKeyFormat
-> SigningKeyFile
-> NewVerificationKeyFile
-> ExceptT ColeClientCmdError IO ()
runToVerification ColeKeyFormat
bKeyFormat SigningKeyFile
skFp NewVerificationKeyFile
nvkFp
SubmitTx NetworkId
network TxFile
fp -> NetworkId -> TxFile -> ExceptT ColeClientCmdError IO ()
runSubmitTx NetworkId
network TxFile
fp
GetTxId TxFile
fp -> TxFile -> ExceptT ColeClientCmdError IO ()
runGetTxId TxFile
fp
SpendGenesisUTxO GenesisFile
genFp NetworkId
nw ColeKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey Address ColeAddr
genRichAddr [TxOut ColeEra]
outs ->
GenesisFile
-> NetworkId
-> ColeKeyFormat
-> NewTxFile
-> SigningKeyFile
-> Address ColeAddr
-> [TxOut ColeEra]
-> ExceptT ColeClientCmdError IO ()
runSpendGenesisUTxO GenesisFile
genFp NetworkId
nw ColeKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey Address ColeAddr
genRichAddr [TxOut ColeEra]
outs
SpendUTxO NetworkId
nw ColeKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey [TxIn]
ins [TxOut ColeEra]
outs ->
NetworkId
-> ColeKeyFormat
-> NewTxFile
-> SigningKeyFile
-> [TxIn]
-> [TxOut ColeEra]
-> ExceptT ColeClientCmdError IO ()
runSpendUTxO NetworkId
nw ColeKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey [TxIn]
ins [TxOut ColeEra]
outs
runNodeCmd :: NodeCmd -> ExceptT ColeClientCmdError IO ()
runNodeCmd :: NodeCmd -> ExceptT ColeClientCmdError IO ()
runNodeCmd (CreateVote NetworkId
nw SigningKeyFile
sKey String
upPropFp Bool
voteBool String
outputFp) =
(ColeVoteError -> ColeClientCmdError)
-> ExceptT ColeVoteError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeVoteError -> ColeClientCmdError
ColeCmdVoteError (ExceptT ColeVoteError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeVoteError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ NetworkId
-> SigningKeyFile
-> String
-> Bool
-> String
-> ExceptT ColeVoteError IO ()
runVoteCreation NetworkId
nw SigningKeyFile
sKey String
upPropFp Bool
voteBool String
outputFp
runNodeCmd (SubmitUpdateProposal NetworkId
network String
proposalFp) =
(ColeUpdateProposalError -> ColeClientCmdError)
-> ExceptT ColeUpdateProposalError IO ()
-> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeUpdateProposalError -> ColeClientCmdError
ColeCmdUpdateProposalError
(ExceptT ColeUpdateProposalError IO ()
-> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeUpdateProposalError IO ()
-> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ NetworkId -> String -> ExceptT ColeUpdateProposalError IO ()
submitColeUpdateProposal NetworkId
network String
proposalFp
runNodeCmd (SubmitVote NetworkId
network String
voteFp) =
(ColeVoteError -> ColeClientCmdError)
-> ExceptT ColeVoteError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeVoteError -> ColeClientCmdError
ColeCmdVoteError (ExceptT ColeVoteError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeVoteError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ NetworkId -> String -> ExceptT ColeVoteError IO ()
submitColeVote NetworkId
network String
voteFp
runNodeCmd (UpdateProposal NetworkId
nw SigningKeyFile
sKey ProtocolVersion
pVer SoftwareVersion
sVer SystemTag
sysTag InstallerHash
insHash String
outputFp ColeProtocolParametersUpdate
params) =
(ColeUpdateProposalError -> ColeClientCmdError)
-> ExceptT ColeUpdateProposalError IO ()
-> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeUpdateProposalError -> ColeClientCmdError
ColeCmdUpdateProposalError
(ExceptT ColeUpdateProposalError IO ()
-> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeUpdateProposalError IO ()
-> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ NetworkId
-> SigningKeyFile
-> ProtocolVersion
-> SoftwareVersion
-> SystemTag
-> InstallerHash
-> String
-> ColeProtocolParametersUpdate
-> ExceptT ColeUpdateProposalError IO ()
runProposalCreation NetworkId
nw SigningKeyFile
sKey ProtocolVersion
pVer SoftwareVersion
sVer SystemTag
sysTag InstallerHash
insHash String
outputFp ColeProtocolParametersUpdate
params
runGenesisCommand :: NewDirectory -> GenesisParameters -> ExceptT ColeClientCmdError IO ()
runGenesisCommand :: NewDirectory
-> GenesisParameters -> ExceptT ColeClientCmdError IO ()
runGenesisCommand NewDirectory
outDir GenesisParameters
params = do
(GenesisData
genData, GeneratedSecrets
genSecrets) <- (ColeGenesisError -> ColeClientCmdError)
-> ExceptT ColeGenesisError IO (GenesisData, GeneratedSecrets)
-> ExceptT ColeClientCmdError IO (GenesisData, GeneratedSecrets)
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeGenesisError -> ColeClientCmdError
ColeCmdGenesisError (ExceptT ColeGenesisError IO (GenesisData, GeneratedSecrets)
-> ExceptT ColeClientCmdError IO (GenesisData, GeneratedSecrets))
-> ExceptT ColeGenesisError IO (GenesisData, GeneratedSecrets)
-> ExceptT ColeClientCmdError IO (GenesisData, GeneratedSecrets)
forall a b. (a -> b) -> a -> b
$ GenesisParameters
-> ExceptT ColeGenesisError IO (GenesisData, GeneratedSecrets)
mkGenesis GenesisParameters
params
(ColeGenesisError -> ColeClientCmdError)
-> ExceptT ColeGenesisError IO ()
-> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeGenesisError -> ColeClientCmdError
ColeCmdGenesisError (ExceptT ColeGenesisError IO ()
-> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeGenesisError IO ()
-> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ NewDirectory
-> GenesisData
-> GeneratedSecrets
-> ExceptT ColeGenesisError IO ()
dumpGenesis NewDirectory
outDir GenesisData
genData GeneratedSecrets
genSecrets
runValidateCBOR :: CBORObject -> FilePath -> ExceptT ColeClientCmdError IO ()
runValidateCBOR :: CBORObject -> String -> ExceptT ColeClientCmdError IO ()
runValidateCBOR CBORObject
cborObject String
fp = do
LByteString
bs <- (HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO LByteString
-> ExceptT ColeClientCmdError IO LByteString
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO LByteString
-> ExceptT ColeClientCmdError IO LByteString)
-> ExceptT HelpersError IO LByteString
-> ExceptT ColeClientCmdError IO LByteString
forall a b. (a -> b) -> a -> b
$ String -> ExceptT HelpersError IO LByteString
readCBOR String
fp
Text
res <- Either ColeClientCmdError Text
-> ExceptT ColeClientCmdError IO Text
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either ColeClientCmdError Text
-> ExceptT ColeClientCmdError IO Text)
-> (Either HelpersError Text -> Either ColeClientCmdError Text)
-> Either HelpersError Text
-> ExceptT ColeClientCmdError IO Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (HelpersError -> ColeClientCmdError)
-> Either HelpersError Text -> Either ColeClientCmdError Text
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first HelpersError -> ColeClientCmdError
ColeCmdHelpersError (Either HelpersError Text -> ExceptT ColeClientCmdError IO Text)
-> Either HelpersError Text -> ExceptT ColeClientCmdError IO Text
forall a b. (a -> b) -> a -> b
$ CBORObject -> LByteString -> Either HelpersError Text
validateCBOR CBORObject
cborObject LByteString
bs
IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ColeClientCmdError IO ())
-> IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Text -> IO ()
putTextLn Text
res
runPrettyPrintCBOR :: FilePath -> ExceptT ColeClientCmdError IO ()
runPrettyPrintCBOR :: String -> ExceptT ColeClientCmdError IO ()
runPrettyPrintCBOR String
fp = do
LByteString
bs <- (HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO LByteString
-> ExceptT ColeClientCmdError IO LByteString
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO LByteString
-> ExceptT ColeClientCmdError IO LByteString)
-> ExceptT HelpersError IO LByteString
-> ExceptT ColeClientCmdError IO LByteString
forall a b. (a -> b) -> a -> b
$ String -> ExceptT HelpersError IO LByteString
readCBOR String
fp
(HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ LByteString -> ExceptT HelpersError IO ()
pPrintCBOR LByteString
bs
runPrettySigningKeyPublic :: ColeKeyFormat -> SigningKeyFile -> ExceptT ColeClientCmdError IO ()
runPrettySigningKeyPublic :: ColeKeyFormat -> SigningKeyFile -> ExceptT ColeClientCmdError IO ()
runPrettySigningKeyPublic ColeKeyFormat
bKeyFormat SigningKeyFile
skF = do
SomeColeSigningKey
sK <- (ColeKeyFailure -> ColeClientCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
readColeSigningKey ColeKeyFormat
bKeyFormat SigningKeyFile
skF
IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ColeClientCmdError IO ())
-> (VerificationKey ColeKey -> IO ())
-> VerificationKey ColeKey
-> ExceptT ColeClientCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> IO ()
putTextLn (Text -> IO ())
-> (VerificationKey ColeKey -> Text)
-> VerificationKey ColeKey
-> IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. VerificationKey ColeKey -> Text
prettyPublicKey (VerificationKey ColeKey -> ExceptT ColeClientCmdError IO ())
-> VerificationKey ColeKey -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ SomeColeSigningKey -> VerificationKey ColeKey
coleWitnessToVerKey SomeColeSigningKey
sK
runMigrateDelegateKeyFrom
:: SigningKeyFile
-> NewSigningKeyFile
-> ExceptT ColeClientCmdError IO ()
runMigrateDelegateKeyFrom :: SigningKeyFile
-> NewSigningKeyFile -> ExceptT ColeClientCmdError IO ()
runMigrateDelegateKeyFrom oldKey :: SigningKeyFile
oldKey@(SigningKeyFile String
fp) (NewSigningKeyFile String
newKey) = do
SomeColeSigningKey
sk <- (ColeKeyFailure -> ColeClientCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
readColeSigningKey ColeKeyFormat
LegacyColeKeyFormat SigningKeyFile
oldKey
SomeColeSigningKey
migratedWitness <- case SomeColeSigningKey
sk of
AColeSigningKeyLegacy (ColeSigningKeyLegacy sKey) ->
SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> (SigningKey ColeKey -> SomeColeSigningKey)
-> SigningKey ColeKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SigningKey ColeKey -> SomeColeSigningKey
AColeSigningKey (SigningKey ColeKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> SigningKey ColeKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ SigningKey -> SigningKey ColeKey
ColeSigningKey SigningKey
sKey
AColeSigningKey SigningKey ColeKey
_ ->
ColeClientCmdError
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left (ColeClientCmdError
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> (ColeKeyFailure -> ColeClientCmdError)
-> ColeKeyFailure
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ColeKeyFailure
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ColeKeyFailure
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ String -> ColeKeyFailure
CannotMigrateFromNonLegacySigningKey String
fp
(HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ())
-> (ByteString -> ExceptT HelpersError IO ())
-> ByteString
-> ExceptT ColeClientCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
newKey (ByteString -> ExceptT ColeClientCmdError IO ())
-> ByteString -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ SomeColeSigningKey -> ByteString
serialiseColeWitness SomeColeSigningKey
migratedWitness
runPrintGenesisHash :: GenesisFile -> ExceptT ColeClientCmdError IO ()
runPrintGenesisHash :: GenesisFile -> ExceptT ColeClientCmdError IO ()
runPrintGenesisHash GenesisFile
genFp = do
Config
genesis <- (ColeGenesisError -> ColeClientCmdError)
-> ExceptT ColeGenesisError IO Config
-> ExceptT ColeClientCmdError IO Config
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeGenesisError -> ColeClientCmdError
ColeCmdGenesisError (ExceptT ColeGenesisError IO Config
-> ExceptT ColeClientCmdError IO Config)
-> ExceptT ColeGenesisError IO Config
-> ExceptT ColeClientCmdError IO Config
forall a b. (a -> b) -> a -> b
$
GenesisFile -> NetworkId -> ExceptT ColeGenesisError IO Config
readGenesis GenesisFile
genFp NetworkId
dummyNetwork
IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ColeClientCmdError IO ())
-> (Text -> IO ()) -> Text -> ExceptT ColeClientCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> IO ()
putTextLn (Text -> ExceptT ColeClientCmdError IO ())
-> Text -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Config -> Text
formatter Config
genesis
where
dummyNetwork :: NetworkId
dummyNetwork :: NetworkId
dummyNetwork = NetworkId
Mainnet
formatter :: Genesis.Config -> Text
formatter :: Config -> Text
formatter = Format Text (AbstractHash Blake2b_256 Raw -> Text)
-> AbstractHash Blake2b_256 Raw -> Text
forall a. Format Text a -> a
F.sformat Format Text (AbstractHash Blake2b_256 Raw -> Text)
forall r algo a. Format r (AbstractHash algo a -> r)
Crypto.hashHexF
(AbstractHash Blake2b_256 Raw -> Text)
-> (Config -> AbstractHash Blake2b_256 Raw) -> Config -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. GenesisHash -> AbstractHash Blake2b_256 Raw
Genesis.unGenesisHash
(GenesisHash -> AbstractHash Blake2b_256 Raw)
-> (Config -> GenesisHash)
-> Config
-> AbstractHash Blake2b_256 Raw
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Config -> GenesisHash
Genesis.configGenesisHash
runPrintSigningKeyAddress
:: ColeKeyFormat
-> NetworkId
-> SigningKeyFile
-> ExceptT ColeClientCmdError IO ()
runPrintSigningKeyAddress :: ColeKeyFormat
-> NetworkId -> SigningKeyFile -> ExceptT ColeClientCmdError IO ()
runPrintSigningKeyAddress ColeKeyFormat
bKeyFormat NetworkId
networkid SigningKeyFile
skF = do
SomeColeSigningKey
sK <- (ColeKeyFailure -> ColeClientCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
readColeSigningKey ColeKeyFormat
bKeyFormat SigningKeyFile
skF
let sKeyAddr :: Text
sKeyAddr = Address ColeAddr -> Text
prettyAddress (Address ColeAddr -> Text)
-> (VerificationKey ColeKey -> Address ColeAddr)
-> VerificationKey ColeKey
-> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. NetworkId -> VerificationKey ColeKey -> Address ColeAddr
makeColeAddress NetworkId
networkid (VerificationKey ColeKey -> Text)
-> VerificationKey ColeKey -> Text
forall a b. (a -> b) -> a -> b
$ SomeColeSigningKey -> VerificationKey ColeKey
coleWitnessToVerKey SomeColeSigningKey
sK
IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ColeClientCmdError IO ())
-> IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Text -> IO ()
putTextLn Text
sKeyAddr
runKeygen :: NewSigningKeyFile -> ExceptT ColeClientCmdError IO ()
runKeygen :: NewSigningKeyFile -> ExceptT ColeClientCmdError IO ()
runKeygen (NewSigningKeyFile String
skF) = do
SigningKey ColeKey
sK <- IO (SigningKey ColeKey)
-> ExceptT ColeClientCmdError IO (SigningKey ColeKey)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SigningKey ColeKey)
-> ExceptT ColeClientCmdError IO (SigningKey ColeKey))
-> IO (SigningKey ColeKey)
-> ExceptT ColeClientCmdError IO (SigningKey ColeKey)
forall a b. (a -> b) -> a -> b
$ AsType ColeKey -> IO (SigningKey ColeKey)
forall keyrole.
Key keyrole =>
AsType keyrole -> IO (SigningKey keyrole)
generateSigningKey AsType ColeKey
AsColeKey
(HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ())
-> (ByteString -> ExceptT HelpersError IO ())
-> ByteString
-> ExceptT ColeClientCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
skF (ByteString -> ExceptT ColeClientCmdError IO ())
-> ByteString -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ SigningKey ColeKey -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes SigningKey ColeKey
sK
runToVerification :: ColeKeyFormat -> SigningKeyFile -> NewVerificationKeyFile -> ExceptT ColeClientCmdError IO ()
runToVerification :: ColeKeyFormat
-> SigningKeyFile
-> NewVerificationKeyFile
-> ExceptT ColeClientCmdError IO ()
runToVerification ColeKeyFormat
bKeyFormat SigningKeyFile
skFp (NewVerificationKeyFile String
vkFp) = do
SomeColeSigningKey
sk <- (ColeKeyFailure -> ColeClientCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
readColeSigningKey ColeKeyFormat
bKeyFormat SigningKeyFile
skFp
let ColeVerificationKey vK = SomeColeSigningKey -> VerificationKey ColeKey
coleWitnessToVerKey SomeColeSigningKey
sk
let vKey :: Text
vKey = Builder -> Text
Builder.toLazyText (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$ VerificationKey -> Builder
Crypto.formatFullVerificationKey VerificationKey
vK
(HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ (String -> Text -> IO ())
-> String -> Text -> ExceptT HelpersError IO ()
forall a.
(String -> a -> IO ()) -> String -> a -> ExceptT HelpersError IO ()
ensureNewFile String -> Text -> IO ()
TL.writeFile String
vkFp Text
vKey
runSubmitTx :: NetworkId -> TxFile -> ExceptT ColeClientCmdError IO ()
runSubmitTx :: NetworkId -> TxFile -> ExceptT ColeClientCmdError IO ()
runSubmitTx NetworkId
network TxFile
fp = do
ATxAux ByteString
tx <- (ColeTxError -> ColeClientCmdError)
-> ExceptT ColeTxError IO (ATxAux ByteString)
-> ExceptT ColeClientCmdError IO (ATxAux ByteString)
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeTxError -> ColeClientCmdError
ColeCmdTxError (ExceptT ColeTxError IO (ATxAux ByteString)
-> ExceptT ColeClientCmdError IO (ATxAux ByteString))
-> ExceptT ColeTxError IO (ATxAux ByteString)
-> ExceptT ColeClientCmdError IO (ATxAux ByteString)
forall a b. (a -> b) -> a -> b
$ TxFile -> ExceptT ColeTxError IO (ATxAux ByteString)
readColeTx TxFile
fp
(ColeTxError -> ColeClientCmdError)
-> ExceptT ColeTxError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeTxError -> ColeClientCmdError
ColeCmdTxError (ExceptT ColeTxError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeTxError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$
NetworkId -> GenTx ColeBlock -> ExceptT ColeTxError IO ()
nodeSubmitTx NetworkId
network (ATxAux ByteString -> GenTx ColeBlock
normalColeTxToGenTx ATxAux ByteString
tx)
runGetTxId :: TxFile -> ExceptT ColeClientCmdError IO ()
runGetTxId :: TxFile -> ExceptT ColeClientCmdError IO ()
runGetTxId TxFile
fp = (ColeTxError -> ColeClientCmdError)
-> ExceptT ColeTxError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeTxError -> ColeClientCmdError
ColeCmdTxError (ExceptT ColeTxError IO () -> ExceptT ColeClientCmdError IO ())
-> ExceptT ColeTxError IO () -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ do
ATxAux ByteString
tx <- TxFile -> ExceptT ColeTxError IO (ATxAux ByteString)
readColeTx TxFile
fp
let txbody :: TxBody ColeEra
txbody = Tx ColeEra -> TxBody ColeEra
forall era. Tx era -> TxBody era
getTxBody (ATxAux ByteString -> Tx ColeEra
ColeTx ATxAux ByteString
tx)
txid :: TxId
txid = TxBody ColeEra -> TxId
forall era. TxBody era -> TxId
getTxId TxBody ColeEra
txbody
IO () -> ExceptT ColeTxError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ColeTxError IO ())
-> IO () -> ExceptT ColeTxError IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> IO ()
BS.putStrLn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ TxId -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytesHex TxId
txid
runSpendGenesisUTxO
:: GenesisFile
-> NetworkId
-> ColeKeyFormat
-> NewTxFile
-> SigningKeyFile
-> Address ColeAddr
-> [TxOut ColeEra]
-> ExceptT ColeClientCmdError IO ()
runSpendGenesisUTxO :: GenesisFile
-> NetworkId
-> ColeKeyFormat
-> NewTxFile
-> SigningKeyFile
-> Address ColeAddr
-> [TxOut ColeEra]
-> ExceptT ColeClientCmdError IO ()
runSpendGenesisUTxO GenesisFile
genesisFile NetworkId
nw ColeKeyFormat
bKeyFormat (NewTxFile String
ctTx) SigningKeyFile
ctKey Address ColeAddr
genRichAddr [TxOut ColeEra]
outs = do
Config
genesis <- (ColeGenesisError -> ColeClientCmdError)
-> ExceptT ColeGenesisError IO Config
-> ExceptT ColeClientCmdError IO Config
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeGenesisError -> ColeClientCmdError
ColeCmdGenesisError (ExceptT ColeGenesisError IO Config
-> ExceptT ColeClientCmdError IO Config)
-> ExceptT ColeGenesisError IO Config
-> ExceptT ColeClientCmdError IO Config
forall a b. (a -> b) -> a -> b
$ GenesisFile -> NetworkId -> ExceptT ColeGenesisError IO Config
readGenesis GenesisFile
genesisFile NetworkId
nw
SomeColeSigningKey
sk <- (ColeKeyFailure -> ColeClientCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
readColeSigningKey ColeKeyFormat
bKeyFormat SigningKeyFile
ctKey
let tx :: Tx ColeEra
tx = Config
-> NetworkId
-> SomeColeSigningKey
-> Address ColeAddr
-> [TxOut ColeEra]
-> Tx ColeEra
txSpendGenesisUTxOColePBFT Config
genesis NetworkId
nw SomeColeSigningKey
sk Address ColeAddr
genRichAddr [TxOut ColeEra]
outs
(HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ())
-> (ByteString -> ExceptT HelpersError IO ())
-> ByteString
-> ExceptT ColeClientCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
ctTx (ByteString -> ExceptT ColeClientCmdError IO ())
-> ByteString -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Tx ColeEra -> ByteString
forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR Tx ColeEra
tx
runSpendUTxO
:: NetworkId
-> ColeKeyFormat
-> NewTxFile
-> SigningKeyFile
-> [TxIn]
-> [TxOut ColeEra]
-> ExceptT ColeClientCmdError IO ()
runSpendUTxO :: NetworkId
-> ColeKeyFormat
-> NewTxFile
-> SigningKeyFile
-> [TxIn]
-> [TxOut ColeEra]
-> ExceptT ColeClientCmdError IO ()
runSpendUTxO NetworkId
nw ColeKeyFormat
bKeyFormat (NewTxFile String
ctTx) SigningKeyFile
ctKey [TxIn]
ins [TxOut ColeEra]
outs = do
SomeColeSigningKey
sk <- (ColeKeyFailure -> ColeClientCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> ColeClientCmdError
ColeCmdKeyFailure (ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT ColeClientCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
readColeSigningKey ColeKeyFormat
bKeyFormat SigningKeyFile
ctKey
let gTx :: Tx ColeEra
gTx = NetworkId
-> SomeColeSigningKey -> [TxIn] -> [TxOut ColeEra] -> Tx ColeEra
txSpendUTxOColePBFT NetworkId
nw SomeColeSigningKey
sk [TxIn]
ins [TxOut ColeEra]
outs
(HelpersError -> ColeClientCmdError)
-> ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ColeClientCmdError
ColeCmdHelpersError (ExceptT HelpersError IO () -> ExceptT ColeClientCmdError IO ())
-> (ByteString -> ExceptT HelpersError IO ())
-> ByteString
-> ExceptT ColeClientCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
ctTx (ByteString -> ExceptT ColeClientCmdError IO ())
-> ByteString -> ExceptT ColeClientCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Tx ColeEra -> ByteString
forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR Tx ColeEra
gTx