{-# LANGUAGE GADTs #-}

module Cardano.CLI.Byron.Run
  ( ByronClientCmdError
  , renderByronClientCmdError
  , runByronClientCommand
  ) where

import           Control.Monad.IO.Class (MonadIO (liftIO))
import           Control.Monad.Trans.Except (ExceptT)
import           Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither, left)
import           Data.Bifunctor (Bifunctor (..))
import qualified Data.ByteString.Char8 as BS
import           Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO 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 Cardano.Chain.Genesis as Genesis

import qualified Cardano.Crypto.Hashing as Crypto
import qualified Cardano.Crypto.Signing as Crypto

import           Cardano.Api hiding (GenesisParameters, UpdateProposal)
import           Cardano.Api.Byron (SomeByronSigningKey (..), Tx (..))

import           Ouroboros.Consensus.Byron.Ledger (ByronBlock)
import           Ouroboros.Consensus.Ledger.SupportsMempool (ApplyTxErr)

import           Cardano.CLI.Byron.Commands
import           Cardano.CLI.Byron.Delegation
import           Cardano.CLI.Byron.Genesis
import           Cardano.CLI.Byron.Key
import           Cardano.CLI.Byron.Query
import           Cardano.CLI.Byron.Tx
import           Cardano.CLI.Byron.UpdateProposal
import           Cardano.CLI.Byron.Vote
import           Cardano.CLI.Helpers
import           Cardano.CLI.Shelley.Commands (ByronKeyFormat (..))
import           Cardano.CLI.Types

-- | Data type that encompasses all the possible errors of the
-- Byron client.
data ByronClientCmdError
  = ByronCmdDelegationError !ByronDelegationError
  | ByronCmdGenesisError !ByronGenesisError
  | ByronCmdHelpersError !HelpersError
  | ByronCmdKeyFailure !ByronKeyFailure
  | ByronCmdQueryError !ByronQueryError
  | ByronCmdTxError !ByronTxError
  | ByronCmdTxSubmitError !(ApplyTxErr ByronBlock)
  | ByronCmdUpdateProposalError !ByronUpdateProposalError
  | ByronCmdVoteError !ByronVoteError
  deriving Int -> ByronClientCmdError -> ShowS
[ByronClientCmdError] -> ShowS
ByronClientCmdError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ByronClientCmdError] -> ShowS
$cshowList :: [ByronClientCmdError] -> ShowS
show :: ByronClientCmdError -> String
$cshow :: ByronClientCmdError -> String
showsPrec :: Int -> ByronClientCmdError -> ShowS
$cshowsPrec :: Int -> ByronClientCmdError -> ShowS
Show

renderByronClientCmdError :: ByronClientCmdError -> Text
renderByronClientCmdError :: ByronClientCmdError -> Text
renderByronClientCmdError ByronClientCmdError
err =
  case ByronClientCmdError
err of
    ByronCmdDelegationError ByronDelegationError
e -> ByronDelegationError -> Text
renderByronDelegationError ByronDelegationError
e
    ByronCmdGenesisError ByronGenesisError
e -> ByronGenesisError -> Text
renderByronGenesisError ByronGenesisError
e
    ByronCmdHelpersError HelpersError
e -> HelpersError -> Text
renderHelpersError HelpersError
e
    ByronCmdKeyFailure ByronKeyFailure
e -> ByronKeyFailure -> Text
renderByronKeyFailure ByronKeyFailure
e
    ByronCmdQueryError ByronQueryError
e -> ByronQueryError -> Text
renderByronQueryError ByronQueryError
e
    ByronCmdTxError ByronTxError
e -> ByronTxError -> Text
renderByronTxError ByronTxError
e
    ByronCmdTxSubmitError ApplyTxErr ByronBlock
e ->
      Text
"Error while submitting Byron tx: " forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (forall a. Show a => a -> String
show ApplyTxErr ByronBlock
e)
    ByronCmdUpdateProposalError ByronUpdateProposalError
e -> ByronUpdateProposalError -> Text
renderByronUpdateProposalError ByronUpdateProposalError
e
    ByronCmdVoteError ByronVoteError
e -> ByronVoteError -> Text
renderByronVoteError ByronVoteError
e

runByronClientCommand :: ByronCommand -> ExceptT ByronClientCmdError IO ()
runByronClientCommand :: ByronCommand -> ExceptT ByronClientCmdError IO ()
runByronClientCommand ByronCommand
c =
  case ByronCommand
c of
    NodeCmd NodeCmd
bc -> NodeCmd -> ExceptT ByronClientCmdError IO ()
runNodeCmd NodeCmd
bc
    Genesis NewDirectory
outDir GenesisParameters
params -> NewDirectory
-> GenesisParameters -> ExceptT ByronClientCmdError IO ()
runGenesisCommand NewDirectory
outDir GenesisParameters
params
    GetLocalNodeTip NetworkId
network -> forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronQueryError -> ByronClientCmdError
ByronCmdQueryError forall a b. (a -> b) -> a -> b
$ NetworkId -> ExceptT ByronQueryError IO ()
runGetLocalNodeTip NetworkId
network
    ValidateCBOR CBORObject
cborObject String
fp -> CBORObject -> String -> ExceptT ByronClientCmdError IO ()
runValidateCBOR CBORObject
cborObject String
fp
    PrettyPrintCBOR String
fp -> String -> ExceptT ByronClientCmdError IO ()
runPrettyPrintCBOR String
fp
    PrettySigningKeyPublic ByronKeyFormat
bKeyFormat SigningKeyFile
skF -> ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronClientCmdError IO ()
runPrettySigningKeyPublic ByronKeyFormat
bKeyFormat SigningKeyFile
skF
    MigrateDelegateKeyFrom SigningKeyFile
oldKey NewSigningKeyFile
nskf ->
       SigningKeyFile
-> NewSigningKeyFile -> ExceptT ByronClientCmdError IO ()
runMigrateDelegateKeyFrom SigningKeyFile
oldKey NewSigningKeyFile
nskf
    PrintGenesisHash GenesisFile
genFp -> GenesisFile -> ExceptT ByronClientCmdError IO ()
runPrintGenesisHash GenesisFile
genFp
    PrintSigningKeyAddress ByronKeyFormat
bKeyFormat NetworkId
networkid SigningKeyFile
skF -> ByronKeyFormat
-> NetworkId -> SigningKeyFile -> ExceptT ByronClientCmdError IO ()
runPrintSigningKeyAddress ByronKeyFormat
bKeyFormat NetworkId
networkid SigningKeyFile
skF
    Keygen NewSigningKeyFile
nskf -> NewSigningKeyFile -> ExceptT ByronClientCmdError IO ()
runKeygen NewSigningKeyFile
nskf
    ToVerification ByronKeyFormat
bKeyFormat SigningKeyFile
skFp NewVerificationKeyFile
nvkFp -> ByronKeyFormat
-> SigningKeyFile
-> NewVerificationKeyFile
-> ExceptT ByronClientCmdError IO ()
runToVerification ByronKeyFormat
bKeyFormat SigningKeyFile
skFp NewVerificationKeyFile
nvkFp
    SubmitTx NetworkId
network TxFile
fp -> NetworkId -> TxFile -> ExceptT ByronClientCmdError IO ()
runSubmitTx NetworkId
network TxFile
fp
    GetTxId TxFile
fp -> TxFile -> ExceptT ByronClientCmdError IO ()
runGetTxId TxFile
fp
    SpendGenesisUTxO GenesisFile
genFp NetworkId
nw ByronKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey Address ByronAddr
genRichAddr [TxOut CtxTx ByronEra]
outs ->
      GenesisFile
-> NetworkId
-> ByronKeyFormat
-> NewTxFile
-> SigningKeyFile
-> Address ByronAddr
-> [TxOut CtxTx ByronEra]
-> ExceptT ByronClientCmdError IO ()
runSpendGenesisUTxO GenesisFile
genFp NetworkId
nw ByronKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey Address ByronAddr
genRichAddr [TxOut CtxTx ByronEra]
outs
    SpendUTxO NetworkId
nw ByronKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey [TxIn]
ins [TxOut CtxTx ByronEra]
outs ->
      NetworkId
-> ByronKeyFormat
-> NewTxFile
-> SigningKeyFile
-> [TxIn]
-> [TxOut CtxTx ByronEra]
-> ExceptT ByronClientCmdError IO ()
runSpendUTxO NetworkId
nw ByronKeyFormat
era NewTxFile
nftx SigningKeyFile
ctKey [TxIn]
ins [TxOut CtxTx ByronEra]
outs


runNodeCmd :: NodeCmd -> ExceptT ByronClientCmdError IO ()
runNodeCmd :: NodeCmd -> ExceptT ByronClientCmdError IO ()
runNodeCmd (CreateVote NetworkId
nw SigningKeyFile
sKey String
upPropFp Bool
voteBool String
outputFp) =
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronVoteError -> ByronClientCmdError
ByronCmdVoteError forall a b. (a -> b) -> a -> b
$ NetworkId
-> SigningKeyFile
-> String
-> Bool
-> String
-> ExceptT ByronVoteError IO ()
runVoteCreation NetworkId
nw SigningKeyFile
sKey String
upPropFp Bool
voteBool String
outputFp

runNodeCmd (SubmitUpdateProposal NetworkId
network String
proposalFp) =
    forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronUpdateProposalError -> ByronClientCmdError
ByronCmdUpdateProposalError
      forall a b. (a -> b) -> a -> b
$ NetworkId -> String -> ExceptT ByronUpdateProposalError IO ()
submitByronUpdateProposal NetworkId
network String
proposalFp

runNodeCmd (SubmitVote NetworkId
network String
voteFp) =
    forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronVoteError -> ByronClientCmdError
ByronCmdVoteError forall a b. (a -> b) -> a -> b
$ NetworkId -> String -> ExceptT ByronVoteError IO ()
submitByronVote NetworkId
network String
voteFp

runNodeCmd (UpdateProposal NetworkId
nw SigningKeyFile
sKey ProtocolVersion
pVer SoftwareVersion
sVer SystemTag
sysTag InstallerHash
insHash String
outputFp ByronProtocolParametersUpdate
params) =
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronUpdateProposalError -> ByronClientCmdError
ByronCmdUpdateProposalError
    forall a b. (a -> b) -> a -> b
$ NetworkId
-> SigningKeyFile
-> ProtocolVersion
-> SoftwareVersion
-> SystemTag
-> InstallerHash
-> String
-> ByronProtocolParametersUpdate
-> ExceptT ByronUpdateProposalError IO ()
runProposalCreation NetworkId
nw SigningKeyFile
sKey ProtocolVersion
pVer SoftwareVersion
sVer SystemTag
sysTag InstallerHash
insHash String
outputFp ByronProtocolParametersUpdate
params

runGenesisCommand :: NewDirectory -> GenesisParameters -> ExceptT ByronClientCmdError IO ()
runGenesisCommand :: NewDirectory
-> GenesisParameters -> ExceptT ByronClientCmdError IO ()
runGenesisCommand NewDirectory
outDir GenesisParameters
params = do
  (GenesisData
genData, GeneratedSecrets
genSecrets) <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronGenesisError -> ByronClientCmdError
ByronCmdGenesisError forall a b. (a -> b) -> a -> b
$ GenesisParameters
-> ExceptT ByronGenesisError IO (GenesisData, GeneratedSecrets)
mkGenesis GenesisParameters
params
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronGenesisError -> ByronClientCmdError
ByronCmdGenesisError forall a b. (a -> b) -> a -> b
$ NewDirectory
-> GenesisData
-> GeneratedSecrets
-> ExceptT ByronGenesisError IO ()
dumpGenesis NewDirectory
outDir GenesisData
genData GeneratedSecrets
genSecrets

runValidateCBOR :: CBORObject -> FilePath -> ExceptT ByronClientCmdError IO ()
runValidateCBOR :: CBORObject -> String -> ExceptT ByronClientCmdError IO ()
runValidateCBOR CBORObject
cborObject String
fp = do
  ByteString
bs <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall a b. (a -> b) -> a -> b
$ String -> ExceptT HelpersError IO ByteString
readCBOR String
fp
  Text
res <- forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall a b. (a -> b) -> a -> b
$ CBORObject -> ByteString -> Either HelpersError Text
validateCBOR CBORObject
cborObject ByteString
bs
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Text -> IO ()
Text.putStrLn Text
res

runPrettyPrintCBOR :: FilePath -> ExceptT ByronClientCmdError IO ()
runPrettyPrintCBOR :: String -> ExceptT ByronClientCmdError IO ()
runPrettyPrintCBOR String
fp = do
  ByteString
bs <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall a b. (a -> b) -> a -> b
$ String -> ExceptT HelpersError IO ByteString
readCBOR String
fp
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall a b. (a -> b) -> a -> b
$ ByteString -> ExceptT HelpersError IO ()
pPrintCBOR ByteString
bs

runPrettySigningKeyPublic :: ByronKeyFormat -> SigningKeyFile -> ExceptT ByronClientCmdError IO ()
runPrettySigningKeyPublic :: ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronClientCmdError IO ()
runPrettySigningKeyPublic ByronKeyFormat
bKeyFormat SigningKeyFile
skF = do
  SomeByronSigningKey
sK <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey ByronKeyFormat
bKeyFormat SigningKeyFile
skF
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IO ()
Text.putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerificationKey ByronKey -> Text
prettyPublicKey forall a b. (a -> b) -> a -> b
$ SomeByronSigningKey -> VerificationKey ByronKey
byronWitnessToVerKey SomeByronSigningKey
sK

runMigrateDelegateKeyFrom
  :: SigningKeyFile
  -- ^ Legacy Byron signing key
  -> NewSigningKeyFile
  -> ExceptT ByronClientCmdError IO ()
runMigrateDelegateKeyFrom :: SigningKeyFile
-> NewSigningKeyFile -> ExceptT ByronClientCmdError IO ()
runMigrateDelegateKeyFrom oldKey :: SigningKeyFile
oldKey@(SigningKeyFile String
fp) (NewSigningKeyFile String
newKey) = do
  SomeByronSigningKey
sk <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey ByronKeyFormat
LegacyByronKeyFormat SigningKeyFile
oldKey
  SomeByronSigningKey
migratedWitness <- case SomeByronSigningKey
sk of
                       AByronSigningKeyLegacy (ByronSigningKeyLegacy SigningKey
sKey) ->
                         forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. SigningKey ByronKey -> SomeByronSigningKey
AByronSigningKey forall a b. (a -> b) -> a -> b
$ SigningKey -> SigningKey ByronKey
ByronSigningKey SigningKey
sKey
                       AByronSigningKey SigningKey ByronKey
_ ->
                         forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ String -> ByronKeyFailure
CannotMigrateFromNonLegacySigningKey String
fp
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
newKey forall a b. (a -> b) -> a -> b
$ SomeByronSigningKey -> ByteString
serialiseByronWitness SomeByronSigningKey
migratedWitness

runPrintGenesisHash :: GenesisFile -> ExceptT ByronClientCmdError IO ()
runPrintGenesisHash :: GenesisFile -> ExceptT ByronClientCmdError IO ()
runPrintGenesisHash GenesisFile
genFp = do
    Config
genesis <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronGenesisError -> ByronClientCmdError
ByronCmdGenesisError forall a b. (a -> b) -> a -> b
$
                 GenesisFile -> NetworkId -> ExceptT ByronGenesisError IO Config
readGenesis GenesisFile
genFp NetworkId
dummyNetwork
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IO ()
Text.putStrLn forall a b. (a -> b) -> a -> b
$ Config -> Text
formatter Config
genesis
  where
    -- For this purpose of getting the hash, it does not matter what network
    -- value we use here.
    dummyNetwork :: NetworkId
    dummyNetwork :: NetworkId
dummyNetwork = NetworkId
Mainnet

    formatter :: Genesis.Config -> Text
    formatter :: Config -> Text
formatter = forall a. Format Text a -> a
F.sformat forall r algo a. Format r (AbstractHash algo a -> r)
Crypto.hashHexF
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenesisHash -> AbstractHash Blake2b_256 Raw
Genesis.unGenesisHash
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> GenesisHash
Genesis.configGenesisHash

runPrintSigningKeyAddress
  :: ByronKeyFormat
  -> NetworkId
  -> SigningKeyFile
  -> ExceptT ByronClientCmdError IO ()
runPrintSigningKeyAddress :: ByronKeyFormat
-> NetworkId -> SigningKeyFile -> ExceptT ByronClientCmdError IO ()
runPrintSigningKeyAddress ByronKeyFormat
bKeyFormat NetworkId
networkid SigningKeyFile
skF = do
  SomeByronSigningKey
sK <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey ByronKeyFormat
bKeyFormat SigningKeyFile
skF
  let sKeyAddr :: Text
sKeyAddr = Address ByronAddr -> Text
prettyAddress forall b c a. (b -> c) -> (a -> b) -> a -> c
. NetworkId -> VerificationKey ByronKey -> Address ByronAddr
makeByronAddress NetworkId
networkid forall a b. (a -> b) -> a -> b
$ SomeByronSigningKey -> VerificationKey ByronKey
byronWitnessToVerKey SomeByronSigningKey
sK
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Text -> IO ()
Text.putStrLn Text
sKeyAddr

runKeygen :: NewSigningKeyFile -> ExceptT ByronClientCmdError IO ()
runKeygen :: NewSigningKeyFile -> ExceptT ByronClientCmdError IO ()
runKeygen (NewSigningKeyFile String
skF)  = do
  SigningKey ByronKey
sK <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall keyrole.
Key keyrole =>
AsType keyrole -> IO (SigningKey keyrole)
generateSigningKey AsType ByronKey
AsByronKey
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
skF forall a b. (a -> b) -> a -> b
$ forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes SigningKey ByronKey
sK

runToVerification :: ByronKeyFormat -> SigningKeyFile -> NewVerificationKeyFile -> ExceptT ByronClientCmdError IO ()
runToVerification :: ByronKeyFormat
-> SigningKeyFile
-> NewVerificationKeyFile
-> ExceptT ByronClientCmdError IO ()
runToVerification ByronKeyFormat
bKeyFormat SigningKeyFile
skFp (NewVerificationKeyFile String
vkFp) = do
  SomeByronSigningKey
sk <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey ByronKeyFormat
bKeyFormat SigningKeyFile
skFp
  let ByronVerificationKey VerificationKey
vK = SomeByronSigningKey -> VerificationKey ByronKey
byronWitnessToVerKey SomeByronSigningKey
sk
  let vKey :: Text
vKey = Builder -> Text
Builder.toLazyText forall a b. (a -> b) -> a -> b
$ VerificationKey -> Builder
Crypto.formatFullVerificationKey VerificationKey
vK
  forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall a b. (a -> b) -> a -> b
$ forall a.
(String -> a -> IO ()) -> String -> a -> ExceptT HelpersError IO ()
ensureNewFile String -> Text -> IO ()
TL.writeFile String
vkFp Text
vKey

runSubmitTx :: NetworkId -> TxFile -> ExceptT ByronClientCmdError IO ()
runSubmitTx :: NetworkId -> TxFile -> ExceptT ByronClientCmdError IO ()
runSubmitTx NetworkId
network TxFile
fp = do
    ATxAux ByteString
tx <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronTxError -> ByronClientCmdError
ByronCmdTxError forall a b. (a -> b) -> a -> b
$ TxFile -> ExceptT ByronTxError IO (ATxAux ByteString)
readByronTx TxFile
fp
    forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronTxError -> ByronClientCmdError
ByronCmdTxError forall a b. (a -> b) -> a -> b
$
      NetworkId -> GenTx ByronBlock -> ExceptT ByronTxError IO ()
nodeSubmitTx NetworkId
network (ATxAux ByteString -> GenTx ByronBlock
normalByronTxToGenTx ATxAux ByteString
tx)

runGetTxId :: TxFile -> ExceptT ByronClientCmdError IO ()
runGetTxId :: TxFile -> ExceptT ByronClientCmdError IO ()
runGetTxId TxFile
fp = forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronTxError -> ByronClientCmdError
ByronCmdTxError forall a b. (a -> b) -> a -> b
$ do
    ATxAux ByteString
tx <- TxFile -> ExceptT ByronTxError IO (ATxAux ByteString)
readByronTx TxFile
fp
    let txbody :: TxBody ByronEra
txbody = forall era. Tx era -> TxBody era
getTxBody (ATxAux ByteString -> Tx ByronEra
ByronTx ATxAux ByteString
tx)
        txid :: TxId
txid   = forall era. TxBody era -> TxId
getTxId TxBody ByronEra
txbody
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ByteString -> IO ()
BS.putStrLn forall a b. (a -> b) -> a -> b
$ forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytesHex TxId
txid

runSpendGenesisUTxO
  :: GenesisFile
  -> NetworkId
  -> ByronKeyFormat
  -> NewTxFile
  -> SigningKeyFile
  -> Address ByronAddr
  -> [TxOut CtxTx ByronEra]
  -> ExceptT ByronClientCmdError IO ()
runSpendGenesisUTxO :: GenesisFile
-> NetworkId
-> ByronKeyFormat
-> NewTxFile
-> SigningKeyFile
-> Address ByronAddr
-> [TxOut CtxTx ByronEra]
-> ExceptT ByronClientCmdError IO ()
runSpendGenesisUTxO GenesisFile
genesisFile NetworkId
nw ByronKeyFormat
bKeyFormat (NewTxFile String
ctTx) SigningKeyFile
ctKey Address ByronAddr
genRichAddr [TxOut CtxTx ByronEra]
outs = do
    Config
genesis <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronGenesisError -> ByronClientCmdError
ByronCmdGenesisError forall a b. (a -> b) -> a -> b
$ GenesisFile -> NetworkId -> ExceptT ByronGenesisError IO Config
readGenesis GenesisFile
genesisFile NetworkId
nw
    SomeByronSigningKey
sk <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey ByronKeyFormat
bKeyFormat SigningKeyFile
ctKey

    let tx :: Tx ByronEra
tx = Config
-> NetworkId
-> SomeByronSigningKey
-> Address ByronAddr
-> [TxOut CtxTx ByronEra]
-> Tx ByronEra
txSpendGenesisUTxOByronPBFT Config
genesis NetworkId
nw SomeByronSigningKey
sk Address ByronAddr
genRichAddr [TxOut CtxTx ByronEra]
outs
    forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
ctTx forall a b. (a -> b) -> a -> b
$ forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR Tx ByronEra
tx

runSpendUTxO
  :: NetworkId
  -> ByronKeyFormat
  -> NewTxFile
  -> SigningKeyFile
  -> [TxIn]
  -> [TxOut CtxTx ByronEra]
  -> ExceptT ByronClientCmdError IO ()
runSpendUTxO :: NetworkId
-> ByronKeyFormat
-> NewTxFile
-> SigningKeyFile
-> [TxIn]
-> [TxOut CtxTx ByronEra]
-> ExceptT ByronClientCmdError IO ()
runSpendUTxO NetworkId
nw ByronKeyFormat
bKeyFormat (NewTxFile String
ctTx) SigningKeyFile
ctKey [TxIn]
ins [TxOut CtxTx ByronEra]
outs = do
    SomeByronSigningKey
sk <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> ByronClientCmdError
ByronCmdKeyFailure forall a b. (a -> b) -> a -> b
$ ByronKeyFormat
-> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey ByronKeyFormat
bKeyFormat SigningKeyFile
ctKey

    let gTx :: Tx ByronEra
gTx = NetworkId
-> SomeByronSigningKey
-> [TxIn]
-> [TxOut CtxTx ByronEra]
-> Tx ByronEra
txSpendUTxOByronPBFT NetworkId
nw SomeByronSigningKey
sk [TxIn]
ins [TxOut CtxTx ByronEra]
outs
    forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT HelpersError -> ByronClientCmdError
ByronCmdHelpersError forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString -> ExceptT HelpersError IO ()
ensureNewFileLBS String
ctTx forall a b. (a -> b) -> a -> b
$ forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR Tx ByronEra
gTx