Skip to content

Commit

Permalink
Add cardano-cli transation view
Browse files Browse the repository at this point in the history
  • Loading branch information
cblp committed Feb 12, 2021
1 parent 22e72e8 commit 8c73d3b
Show file tree
Hide file tree
Showing 5 changed files with 144 additions and 14 deletions.
1 change: 1 addition & 0 deletions cardano-cli/cardano-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ library
Cardano.CLI.Shelley.Run.Key
Cardano.CLI.Shelley.Run.Node
Cardano.CLI.Shelley.Run.Pool
Cardano.CLI.Shelley.Run.Pretty
Cardano.CLI.Shelley.Run.Query
Cardano.CLI.Shelley.Run.StakeAddress
Cardano.CLI.Shelley.Run.TextView
Expand Down
8 changes: 7 additions & 1 deletion cardano-cli/src/Cardano/CLI/Shelley/Commands.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module Cardano.CLI.Shelley.Commands
, WitnessFile (..)
, TxBodyFile (..)
, TxFile (..)
, InputTxFile (..)
, VerificationKeyBase64 (..)
, GenesisKeyFile (..)
, MetadataFile (..)
Expand Down Expand Up @@ -192,7 +193,11 @@ data TransactionCmd
TxOutCount
TxShelleyWitnessCount
TxByronWitnessCount
| TxGetTxId (Either TxBodyFile TxFile)
| TxGetTxId InputTxFile
| TxView InputTxFile
deriving Show

data InputTxFile = InputTxBodyFile TxBodyFile | InputTxFile TxFile
deriving Show

data ProtocolParamsSourceSpec
Expand All @@ -217,6 +222,7 @@ renderTransactionCmd cmd =
TxMintedPolicyId {} -> "transaction policyid"
TxCalculateMinFee {} -> "transaction calculate-min-fee"
TxGetTxId {} -> "transaction txid"
TxView {} -> "transaction view"

data NodeCmd
= NodeKeyGenCold VerificationKeyFile SigningKeyFile OpCertCounterFile
Expand Down
16 changes: 11 additions & 5 deletions cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -476,6 +476,8 @@ pTransaction =
(Opt.info pTransactionCalculateMinFee $ Opt.progDesc "Calculate the minimum fee for a transaction")
, subParser "txid"
(Opt.info pTransactionId $ Opt.progDesc "Print a transaction identifier")
, subParser "view" $
Opt.info pTransactionView $ Opt.progDesc "Print a transaction"
]
where
assembleInfo :: ParserInfo TransactionCmd
Expand Down Expand Up @@ -551,9 +553,10 @@ pTransaction =
ParamsFromFile <$> pProtocolParamsFile

pTransactionId :: Parser TransactionCmd
pTransactionId = TxGetTxId <$> (Left <$> pTxBodyFile Input
<|> Right <$> pTxFile Input)
pTransactionId = TxGetTxId <$> pInputTxFile

pTransactionView :: Parser TransactionCmd
pTransactionView = TxView <$> pInputTxFile

pNodeCmd :: Parser NodeCmd
pNodeCmd =
Expand Down Expand Up @@ -1651,7 +1654,7 @@ pTxBodyFile fdir =
( Opt.strOption
( Opt.long optName
<> Opt.metavar "FILE"
<> Opt.help (show fdir ++ " filepath of the TxBody.")
<> Opt.help (show fdir ++ " filepath of the JSON TxBody.")
<> Opt.completer (Opt.bashCompleter "file")
)
<|>
Expand All @@ -1673,7 +1676,7 @@ pTxFile fdir =
( Opt.strOption
( Opt.long optName
<> Opt.metavar "FILE"
<> Opt.help (show fdir ++ " filepath of the Tx.")
<> Opt.help (show fdir ++ " filepath of the JSON Tx.")
<> Opt.completer (Opt.bashCompleter "file")
)
<|>
Expand All @@ -1688,6 +1691,10 @@ pTxFile fdir =
Input -> "tx-file"
Output -> "out-file"

pInputTxFile :: Parser InputTxFile
pInputTxFile =
InputTxBodyFile <$> pTxBodyFile Input <|> InputTxFile <$> pTxFile Input

pTxInCount :: Parser TxInCount
pTxInCount =
TxInCount <$>
Expand Down Expand Up @@ -2453,4 +2460,3 @@ readerFromParsecParser p =
subParser :: String -> ParserInfo a -> Parser a
subParser availableCommand pInfo =
Opt.hsubparser $ Opt.command availableCommand pInfo <> Opt.metavar availableCommand

107 changes: 107 additions & 0 deletions cardano-cli/src/Cardano/CLI/Shelley/Run/Pretty.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,107 @@
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Cardano.CLI.Shelley.Run.Pretty (prettyTx) where

import Cardano.Api
(ShelleyBasedEra (ShelleyBasedEraAllegra, ShelleyBasedEraMary, ShelleyBasedEraShelley))
import Cardano.Api.Byron (TxBody (ByronTxBody))
import Cardano.Api.Shelley (TxBody (ShelleyTxBody))
import Cardano.CLI.Helpers (textShow)
import qualified Cardano.Ledger.ShelleyMA.TxBody as ShelleyMA
import Cardano.Prelude
import Data.Aeson as JSON (Value, object, (.=))
import Data.Aeson.Encode.Pretty (Config (confCompare), defConfig, encodePretty')
import qualified Shelley.Spec.Ledger.API as Shelley

prettyTx :: TxBody era -> LByteString
prettyTx body0 =
encodePretty' defConfig{confCompare = compare} $
object $
case body0 of
ByronTxBody tx -> ["era" .= ("Byron" :: Text), "tx" .= tx]
ShelleyTxBody ShelleyBasedEraShelley body aux ->
[ "era" .= ("Shelley" :: Text)
, "inputs" .= _inputs
, "outputs" .= _outputs
, "certificates" .= fmap textShow _certs
, "withdrawals" .= withdrawals
, "fee" .= _txfee
, "timetolive" .= _ttl
, "update" .= fmap textShow _txUpdate
, "metadata_hash" .= fmap textShow _mdHash
, "auxiliary_data" .= fmap textShow aux
]
where
Shelley.TxBody
{ _inputs
, _outputs
, _certs
, _wdrls
, _txfee
, _ttl
, _txUpdate
, _mdHash
} =
body
Shelley.Wdrl withdrawals = _wdrls
ShelleyTxBody ShelleyBasedEraAllegra body aux ->
[ "era" .= ("Allegra" :: Text)
, "inputs" .= inputs
, "outputs" .= outputs
, "certificates" .= fmap textShow certificates
, "withdrawals" .= withdrawals
, "fee" .= txfee
, "validity_interval" .= prettyValidityInterval validity
, "update" .= fmap textShow update
, "auxiliary_data_hash" .= fmap textShow adHash
, "mint" .= mint
, "auxiliary_data" .= fmap textShow aux
]
where
ShelleyMA.TxBody
inputs
outputs
certificates
(Shelley.Wdrl withdrawals)
txfee
validity
update
adHash
mint =
body
ShelleyTxBody ShelleyBasedEraMary body aux ->
[ "era" .= ("Mary" :: Text)
, "inputs" .= inputs
, "outputs" .= outputs
, "certificates" .= fmap textShow certificates
, "withdrawals" .= withdrawals
, "fee" .= txfee
, "validity_interval" .= prettyValidityInterval validity
, "update" .= fmap textShow update
, "auxiliary_data_hash" .= fmap textShow adHash
, "mint" .= mint
, "auxiliary_data" .= fmap textShow aux
]
where
ShelleyMA.TxBody
inputs
outputs
certificates
(Shelley.Wdrl withdrawals)
txfee
validity
update
adHash
mint =
body

prettyValidityInterval :: ShelleyMA.ValidityInterval -> JSON.Value
prettyValidityInterval
ShelleyMA.ValidityInterval{invalidBefore, invalidHereafter} =
object
[ "invalid_before" .= invalidBefore
, "invalid_hereafter" .= invalidHereafter
]
26 changes: 18 additions & 8 deletions cardano-cli/src/Cardano/CLI/Shelley/Run/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import Prelude (String)

import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Lazy.Char8 as LBS
import qualified Data.Text as Text
import Data.Type.Equality (TestEquality (..))

Expand Down Expand Up @@ -47,6 +47,7 @@ import Cardano.CLI.Shelley.Key (InputDecodeError, readSigningKeyFileAn
import Cardano.CLI.Shelley.Parsers
import Cardano.CLI.Shelley.Run.Genesis (ShelleyGenesisCmdError (..), readShelleyGenesis,
renderShelleyGenesisCmdError)
import Cardano.CLI.Shelley.Run.Pretty (prettyTx)
import Cardano.CLI.Types

data ShelleyTxCmdError
Expand Down Expand Up @@ -205,15 +206,14 @@ runTransactionCmd cmd =
nShelleyKeyWitnesses nByronKeyWitnesses ->
runTxCalculateMinFee txbody mnw pGenesisOrParamsFile nInputs nOutputs
nShelleyKeyWitnesses nByronKeyWitnesses
TxGetTxId txinfile ->
runTxGetTxId txinfile
TxGetTxId txinfile -> runTxGetTxId txinfile
TxView txinfile -> runTxView txinfile
TxMintedPolicyId sFile -> runTxCreatePolicyId sFile
TxCreateWitness txBodyfile witSignData mbNw outFile ->
runTxCreateWitness txBodyfile witSignData mbNw outFile
TxAssembleTxBodyWitness txBodyFile witnessFile outFile ->
runTxSignWitness txBodyFile witnessFile outFile


-- ----------------------------------------------------------------------------
-- Building transactions
--
Expand Down Expand Up @@ -773,17 +773,27 @@ mkShelleyBootstrapWitnesses mnw txBody =
mapM (mkShelleyBootstrapWitness mnw txBody)


runTxGetTxId :: Either TxBodyFile TxFile -> ExceptT ShelleyTxCmdError IO ()
runTxGetTxId :: InputTxFile -> ExceptT ShelleyTxCmdError IO ()
runTxGetTxId txfile = do
InAnyCardanoEra _era txbody <-
case txfile of
Left (TxBodyFile txbodyFile) -> readFileTxBody txbodyFile
Right (TxFile txFile) -> do
InputTxBodyFile (TxBodyFile txbodyFile) -> readFileTxBody txbodyFile
InputTxFile (TxFile txFile) -> do
InAnyCardanoEra era tx <- readFileTx txFile
return (InAnyCardanoEra era (getTxBody tx))
return . InAnyCardanoEra era $ getTxBody tx

liftIO $ BS.putStrLn $ serialiseToRawBytesHex (getTxId txbody)

runTxView :: InputTxFile -> ExceptT ShelleyTxCmdError IO ()
runTxView txfile = do
InAnyCardanoEra _era txbody <-
case txfile of
InputTxBodyFile (TxBodyFile txbodyFile) -> readFileTxBody txbodyFile
InputTxFile (TxFile txFile) -> do
InAnyCardanoEra era tx <- readFileTx txFile
return . InAnyCardanoEra era $ getTxBody tx
liftIO $ LBS.putStrLn $ prettyTx txbody

runTxCreateWitness
:: TxBodyFile
-> WitnessSigningData
Expand Down

0 comments on commit 8c73d3b

Please sign in to comment.