Skip to content

Commit

Permalink
Build simple raw transaction in cardano client
Browse files Browse the repository at this point in the history
This replaces the call to `cardano-cli transaction build-raw ...` by
Haskell function based on Cardano.Api
  • Loading branch information
abailly-iohk committed Oct 25, 2021
1 parent 845c473 commit c289f19
Show file tree
Hide file tree
Showing 3 changed files with 47 additions and 28 deletions.
47 changes: 29 additions & 18 deletions local-cluster/src/CardanoClient.hs
Expand Up @@ -6,24 +6,11 @@ module CardanoClient where

import Hydra.Prelude

import Cardano.Api (
Address,
AddressAny (AddressShelley),
AlonzoEra,
CardanoEra (AlonzoEra),
ConsensusModeParams (CardanoModeParams),
EpochSlots (EpochSlots),
EraInMode (AlonzoEraInCardanoMode),
LocalNodeConnectInfo (LocalNodeConnectInfo),
NetworkId,
QueryInEra (QueryInShelleyBasedEra),
QueryInMode (QueryInEra),
QueryInShelleyBasedEra (QueryUTxO),
QueryUTxOFilter (QueryUTxOByAddress),
ShelleyAddr,
UTxO,
)
import Cardano.Api.Shelley (ShelleyBasedEra (ShelleyBasedEraAlonzo), VerificationKey (PaymentVerificationKey))
-- We use quite a lot of stuff from the API so enumerating them all is pointless and
-- clutters the code
import Cardano.Api

import Cardano.Api.Shelley (VerificationKey (PaymentVerificationKey))
import Cardano.CLI.Shelley.Run.Address (buildShelleyAddress)
import Cardano.CLI.Shelley.Run.Query (executeQuery)
import qualified Cardano.Ledger.Keys as Keys
Expand Down Expand Up @@ -67,9 +54,33 @@ queryUtxo networkId socket addresses =
Left err -> throwIO $ QueryException (show err)
Right utxo -> pure utxo

-- | Build a "raw" transaction from a bunch of inputs, outputs and fees.
transactionBuildRaw :: [TxIn] -> [TxOut AlonzoEra] -> SlotNo -> Lovelace -> IO (TxBody AlonzoEra)
transactionBuildRaw txIns txOuts invalidAfter fee = do
let txBodyContent =
TxBodyContent
(map (,BuildTxWith $ KeyWitness KeyWitnessForSpending) txIns)
(TxInsCollateral CollateralInAlonzoEra [])
txOuts
(TxFeeExplicit TxFeesExplicitInAlonzoEra fee)
(TxValidityNoLowerBound, TxValidityUpperBound ValidityUpperBoundInAlonzoEra invalidAfter)
(TxMetadataInEra TxMetadataInAlonzoEra (TxMetadata mempty))
(TxAuxScripts AuxScriptsInAlonzoEra [])
(BuildTxWith TxExtraScriptDataNone)
(TxExtraKeyWitnesses ExtraKeyWitnessesInAlonzoEra [])
(BuildTxWith Nothing)
(TxWithdrawals WithdrawalsInAlonzoEra [])
(TxCertificates CertificatesInAlonzoEra [] (BuildTxWith mempty))
TxUpdateProposalNone
(TxMintValue MultiAssetInAlonzoEra mempty (BuildTxWith mempty))
TxScriptValidityNone

either (throwIO . TransactionBuildRawException . show) pure $ makeTransactionBody txBodyContent

data CardanoClientException
= BuildAddressException Text
| QueryException Text
| TransactionBuildRawException Text
deriving (Show)

instance Exception CardanoClientException
20 changes: 16 additions & 4 deletions local-cluster/test/Test/LocalClusterSpec.hs
Expand Up @@ -6,18 +6,23 @@ import Test.Hydra.Prelude
import Cardano.Api (
Address,
Lovelace,
MultiAssetSupportedInEra (MultiAssetInAlonzoEra),
ShelleyAddr,
TxIn (TxIn),
TxIx (TxIx),
TxOut (TxOut),
TxOutDatumHash (TxOutDatumHashNone),
TxOutValue (TxOutAdaOnly, TxOutValue),
UTxO (..),
lovelaceToValue,
selectLovelace,
serialiseToBech32,
serialiseToRawBytesHexText,
shelleyAddressInEra,
writeFileTextEnvelope,
)
import Cardano.Api.Shelley (Lovelace (Lovelace))
import CardanoClient (buildAddress, queryUtxo)
import CardanoClient (buildAddress, queryUtxo, transactionBuildRaw)
import CardanoCluster (ClusterConfig (..), ClusterLog (..), RunningCluster (..), keysFor, testClusterConfig, withCluster)
import CardanoNode (ChainTip (..), RunningNode (..), cliQueryTip)
import qualified Data.Map as Map
Expand Down Expand Up @@ -66,12 +71,18 @@ assertCanSpendInitialFunds = \case
TxOutAdaOnly _ l -> l
TxOutValue _ v -> selectLovelace v

runTestScript (parentStateDirectory </> "node-" <> show nodeId) addr txIn amount socket
nodeDirectory = parentStateDirectory </> "node-" <> show nodeId
rawFilePath = nodeDirectory </> "tx.raw"

rawTx <- transactionBuildRaw [txIn] [TxOut (shelleyAddressInEra addr) (TxOutValue MultiAssetInAlonzoEra (lovelaceToValue 100_000_000)) TxOutDatumHashNone] 0 0
writeFileTextEnvelope rawFilePath Nothing rawTx >>= either (error . show) pure

runTestScript nodeDirectory addr txIn amount rawFilePath socket
_ ->
error "empty cluster?"

runTestScript :: FilePath -> Address ShelleyAddr -> TxIn -> Lovelace -> FilePath -> IO ()
runTestScript nodeDirectory addr (TxIn txId (TxIx txIx)) (Lovelace amount) socket = do
runTestScript :: FilePath -> Address ShelleyAddr -> TxIn -> Lovelace -> FilePath -> FilePath -> IO ()
runTestScript nodeDirectory addr (TxIn txId (TxIx txIx)) (Lovelace amount) rawTx socket = do
inputScript <- Pkg.getDataFileName "test_submit.sh"
currentEnv <- getEnvironment
let scriptOutput = nodeDirectory </> "test_submit.out"
Expand All @@ -90,6 +101,7 @@ runTestScript nodeDirectory addr (TxIn txId (TxIx txIx)) (Lovelace amount) socke
, -- NOTE(AB): there is a renderTxIn function in the API which is not exposed (yet?)
unpack $ serialiseToRawBytesHexText txId <> "#" <> show txIx
, show amount
, rawTx
]
)
{ env = Just (socketEnv : baseEnv)
Expand Down
8 changes: 2 additions & 6 deletions local-cluster/test_submit.sh
Expand Up @@ -8,15 +8,11 @@ set -vx
utxo_addr=$1
utxo=$2
amount=$3
raw_file=$4

transfer_amount=100000000

# dispatch some ADAs to alice
cardano-cli transaction build-raw --tx-in $utxo \
--tx-out $utxo_addr+$transfer_amount \
--invalid-hereafter 0 --fee 0 --out-file tx.draft

fees=$(cardano-cli transaction calculate-min-fee --tx-body-file tx.draft --tx-in-count 1 --tx-out-count 2 --witness-count 1 --testnet-magic 42 --genesis genesis-shelley.json | cut -d ' ' -f1)
fees=$(cardano-cli transaction calculate-min-fee --tx-body-file $raw_file --tx-in-count 1 --tx-out-count 2 --witness-count 1 --testnet-magic 42 --genesis genesis-shelley.json | cut -d ' ' -f1)
slot=$(cardano-cli query tip --testnet-magic 42 | jq .slot)

cardano-cli transaction build-raw --tx-in $alice_txin \
Expand Down

0 comments on commit c289f19

Please sign in to comment.