{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
module Cardano.CLI.Byron.Tx
( ByronTxError(..)
, TxFile(..)
, NewTxFile(..)
, prettyAddress
, readByronTx
, normalByronTxToGenTx
, txSpendGenesisUTxOByronPBFT
, txSpendUTxOByronPBFT
, nodeSubmitTx
, renderByronTxError
, fromCborTxAux
, toCborTxAux
, ScriptValidity(..)
)
where
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Except (ExceptT)
import Control.Monad.Trans.Except.Extra (firstExceptT, left, newExceptT)
import Data.Bifunctor (Bifunctor (..))
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as LB
import qualified Data.List as List
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, mapMaybe)
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import Formatting (sformat, (%))
import Cardano.Api
import qualified Cardano.Binary as Binary
import qualified Cardano.Chain.Common as Common
import Cardano.Chain.Genesis as Genesis
import qualified Cardano.Chain.UTxO as UTxO
import qualified Cardano.Crypto.Signing as Crypto
import Cardano.Api.Byron
import Cardano.CLI.Byron.Key (byronWitnessToVerKey)
import Cardano.CLI.Types (TxFile (..))
import Ouroboros.Consensus.Byron.Ledger (ByronBlock, GenTx (..))
import qualified Ouroboros.Consensus.Byron.Ledger as Byron
import Ouroboros.Consensus.Cardano.Block (EraMismatch (..))
import qualified Ouroboros.Network.Protocol.LocalTxSubmission.Client as Net.Tx
data ByronTxError
= TxDeserialisationFailed !FilePath !Binary.DecoderError
| ByronTxSubmitError !Text
| ByronTxSubmitErrorEraMismatch !EraMismatch
| EnvSocketError !EnvSocketError
deriving Int -> ByronTxError -> ShowS
[ByronTxError] -> ShowS
ByronTxError -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ByronTxError] -> ShowS
$cshowList :: [ByronTxError] -> ShowS
show :: ByronTxError -> [Char]
$cshow :: ByronTxError -> [Char]
showsPrec :: Int -> ByronTxError -> ShowS
$cshowsPrec :: Int -> ByronTxError -> ShowS
Show
renderByronTxError :: ByronTxError -> Text
renderByronTxError :: ByronTxError -> Text
renderByronTxError ByronTxError
err =
case ByronTxError
err of
ByronTxSubmitError Text
res -> Text
"Error while submitting tx: " forall a. Semigroup a => a -> a -> a
<> Text
res
ByronTxSubmitErrorEraMismatch EraMismatch{Text
ledgerEraName :: EraMismatch -> Text
ledgerEraName :: Text
ledgerEraName, Text
otherEraName :: EraMismatch -> Text
otherEraName :: Text
otherEraName} ->
Text
"The era of the node and the tx do not match. " forall a. Semigroup a => a -> a -> a
<>
Text
"The node is running in the " forall a. Semigroup a => a -> a -> a
<> Text
ledgerEraName forall a. Semigroup a => a -> a -> a
<>
Text
" era, but the transaction is for the " forall a. Semigroup a => a -> a -> a
<> Text
otherEraName forall a. Semigroup a => a -> a -> a
<> Text
" era."
TxDeserialisationFailed [Char]
txFp DecoderError
decErr ->
Text
"Transaction deserialisation failed at " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
textShow [Char]
txFp forall a. Semigroup a => a -> a -> a
<> Text
" Error: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
textShow DecoderError
decErr
EnvSocketError EnvSocketError
envSockErr -> EnvSocketError -> Text
renderEnvSocketError EnvSocketError
envSockErr
newtype NewTxFile =
NewTxFile FilePath
deriving (NewTxFile -> NewTxFile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewTxFile -> NewTxFile -> Bool
$c/= :: NewTxFile -> NewTxFile -> Bool
== :: NewTxFile -> NewTxFile -> Bool
$c== :: NewTxFile -> NewTxFile -> Bool
Eq, Eq NewTxFile
NewTxFile -> NewTxFile -> Bool
NewTxFile -> NewTxFile -> Ordering
NewTxFile -> NewTxFile -> NewTxFile
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NewTxFile -> NewTxFile -> NewTxFile
$cmin :: NewTxFile -> NewTxFile -> NewTxFile
max :: NewTxFile -> NewTxFile -> NewTxFile
$cmax :: NewTxFile -> NewTxFile -> NewTxFile
>= :: NewTxFile -> NewTxFile -> Bool
$c>= :: NewTxFile -> NewTxFile -> Bool
> :: NewTxFile -> NewTxFile -> Bool
$c> :: NewTxFile -> NewTxFile -> Bool
<= :: NewTxFile -> NewTxFile -> Bool
$c<= :: NewTxFile -> NewTxFile -> Bool
< :: NewTxFile -> NewTxFile -> Bool
$c< :: NewTxFile -> NewTxFile -> Bool
compare :: NewTxFile -> NewTxFile -> Ordering
$ccompare :: NewTxFile -> NewTxFile -> Ordering
Ord, Int -> NewTxFile -> ShowS
[NewTxFile] -> ShowS
NewTxFile -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [NewTxFile] -> ShowS
$cshowList :: [NewTxFile] -> ShowS
show :: NewTxFile -> [Char]
$cshow :: NewTxFile -> [Char]
showsPrec :: Int -> NewTxFile -> ShowS
$cshowsPrec :: Int -> NewTxFile -> ShowS
Show, [Char] -> NewTxFile
forall a. ([Char] -> a) -> IsString a
fromString :: [Char] -> NewTxFile
$cfromString :: [Char] -> NewTxFile
IsString)
prettyAddress :: Address ByronAddr -> Text
prettyAddress :: Address ByronAddr -> Text
prettyAddress (ByronAddress Address
addr) = forall a. Format Text a -> a
sformat
(forall r. Format r (Address -> r)
Common.addressF forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (Address -> Text) (Address -> Text)
"\n" forall r a r'. Format r a -> Format r' r -> Format r' a
% forall r. Format r (Address -> r)
Common.addressDetailedF)
Address
addr Address
addr
readByronTx :: TxFile -> ExceptT ByronTxError IO (UTxO.ATxAux ByteString)
readByronTx :: TxFile -> ExceptT ByronTxError IO (ATxAux ByteString)
readByronTx (TxFile [Char]
fp) = do
ByteString
txBS <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ [Char] -> IO ByteString
LB.readFile [Char]
fp
case ByteString -> Either DecoderError (ATxAux ByteString)
fromCborTxAux ByteString
txBS of
Left DecoderError
e -> forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left forall a b. (a -> b) -> a -> b
$ [Char] -> DecoderError -> ByronTxError
TxDeserialisationFailed [Char]
fp DecoderError
e
Right ATxAux ByteString
tx -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ATxAux ByteString
tx
normalByronTxToGenTx :: UTxO.ATxAux ByteString -> GenTx ByronBlock
normalByronTxToGenTx :: ATxAux ByteString -> GenTx ByronBlock
normalByronTxToGenTx ATxAux ByteString
tx' = TxId -> ATxAux ByteString -> GenTx ByronBlock
Byron.ByronTx (ATxAux ByteString -> TxId
Byron.byronIdTx ATxAux ByteString
tx') ATxAux ByteString
tx'
genesisUTxOTxIn :: Genesis.Config -> Crypto.VerificationKey -> Common.Address -> UTxO.TxIn
genesisUTxOTxIn :: Config -> VerificationKey -> Address -> TxIn
genesisUTxOTxIn Config
gc VerificationKey
vk Address
genAddr =
Maybe TxIn -> TxIn
handleMissingAddr forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Address
genAddr Map Address (TxIn, TxOut)
initialUtxo
where
initialUtxo :: Map Common.Address (UTxO.TxIn, UTxO.TxOut)
initialUtxo :: Map Address (TxIn, TxOut)
initialUtxo =
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\(TxIn
inp, TxOut
out) -> TxIn -> Address -> TxOut -> (Address, (TxIn, TxOut))
mkEntry TxIn
inp Address
genAddr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> VerificationKey -> TxOut -> Maybe TxOut
keyMatchesUTxO VerificationKey
vk TxOut
out)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(CompactTxIn, CompactTxOut)] -> [(TxIn, TxOut)]
fromCompactTxInTxOutList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
Map.toList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxO -> Map CompactTxIn CompactTxOut
UTxO.unUTxO
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> UTxO
UTxO.genesisUtxo
forall a b. (a -> b) -> a -> b
$ Config
gc
where
mkEntry :: UTxO.TxIn
-> Common.Address
-> UTxO.TxOut
-> (Common.Address, (UTxO.TxIn, UTxO.TxOut))
mkEntry :: TxIn -> Address -> TxOut -> (Address, (TxIn, TxOut))
mkEntry TxIn
inp Address
addr TxOut
out = (Address
addr, (TxIn
inp, TxOut
out))
fromCompactTxInTxOutList :: [(UTxO.CompactTxIn, UTxO.CompactTxOut)]
-> [(UTxO.TxIn, UTxO.TxOut)]
fromCompactTxInTxOutList :: [(CompactTxIn, CompactTxOut)] -> [(TxIn, TxOut)]
fromCompactTxInTxOutList =
forall a b. (a -> b) -> [a] -> [b]
map (forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap CompactTxIn -> TxIn
UTxO.fromCompactTxIn CompactTxOut -> TxOut
UTxO.fromCompactTxOut)
keyMatchesUTxO :: Crypto.VerificationKey -> UTxO.TxOut -> Maybe UTxO.TxOut
keyMatchesUTxO :: VerificationKey -> TxOut -> Maybe TxOut
keyMatchesUTxO VerificationKey
key TxOut
out =
if VerificationKey -> Address -> Bool
Common.checkVerKeyAddress VerificationKey
key (TxOut -> Address
UTxO.txOutAddress TxOut
out)
then forall a. a -> Maybe a
Just TxOut
out else forall a. Maybe a
Nothing
handleMissingAddr :: Maybe UTxO.TxIn -> UTxO.TxIn
handleMissingAddr :: Maybe TxIn -> TxIn
handleMissingAddr = forall a. a -> Maybe a -> a
fromMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => [Char] -> a
error
forall a b. (a -> b) -> a -> b
$ [Char]
"\nGenesis UTxO has no address\n"
forall a. Semigroup a => a -> a -> a
<> Text -> [Char]
Text.unpack (Address ByronAddr -> Text
prettyAddress (Address -> Address ByronAddr
ByronAddress Address
genAddr))
forall a. Semigroup a => a -> a -> a
<> [Char]
"\n\nIt has the following, though:\n\n"
forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
List.concatMap (Text -> [Char]
Text.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address ByronAddr -> Text
prettyAddress forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Address ByronAddr
ByronAddress) (forall k a. Map k a -> [k]
Map.keys Map Address (TxIn, TxOut)
initialUtxo)
txSpendGenesisUTxOByronPBFT
:: Genesis.Config
-> NetworkId
-> SomeByronSigningKey
-> Address ByronAddr
-> [TxOut CtxTx ByronEra]
-> Tx ByronEra
txSpendGenesisUTxOByronPBFT :: Config
-> NetworkId
-> SomeByronSigningKey
-> Address ByronAddr
-> [TxOut CtxTx ByronEra]
-> Tx ByronEra
txSpendGenesisUTxOByronPBFT Config
gc NetworkId
nId SomeByronSigningKey
sk (ByronAddress Address
bAddr) [TxOut CtxTx ByronEra]
outs = do
let txBodyCont :: TxBodyContent BuildTx ByronEra
txBodyCont =
forall build era.
TxIns build era
-> TxInsCollateral era
-> TxInsReference build era
-> [TxOut CtxTx era]
-> TxTotalCollateral era
-> TxReturnCollateral CtxTx era
-> TxFee era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
-> TxMetadataInEra era
-> TxAuxScripts era
-> TxExtraKeyWitnesses era
-> BuildTxWith build (Maybe ProtocolParameters)
-> TxWithdrawals build era
-> TxCertificates build era
-> TxUpdateProposal era
-> TxMintValue build era
-> TxScriptValidity era
-> TxBodyContent build era
TxBodyContent
[ (TxIn -> TxIn
fromByronTxIn TxIn
txIn
, forall a. a -> BuildTxWith BuildTx a
BuildTxWith (forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era
KeyWitness KeyWitnessInCtx WitCtxTxIn
KeyWitnessForSpending))
]
forall era. TxInsCollateral era
TxInsCollateralNone
forall build era. TxInsReference build era
TxInsReferenceNone
[TxOut CtxTx ByronEra]
outs
forall era. TxTotalCollateral era
TxTotalCollateralNone
forall ctx era. TxReturnCollateral ctx era
TxReturnCollateralNone
(forall era. TxFeesImplicitInEra era -> TxFee era
TxFeeImplicit TxFeesImplicitInEra ByronEra
TxFeesImplicitInByronEra)
( forall era. TxValidityLowerBound era
TxValidityNoLowerBound
, forall era.
ValidityNoUpperBoundSupportedInEra era -> TxValidityUpperBound era
TxValidityNoUpperBound ValidityNoUpperBoundSupportedInEra ByronEra
ValidityNoUpperBoundInByronEra
)
forall era. TxMetadataInEra era
TxMetadataNone
forall era. TxAuxScripts era
TxAuxScriptsNone
forall era. TxExtraKeyWitnesses era
TxExtraKeyWitnessesNone
(forall a. a -> BuildTxWith BuildTx a
BuildTxWith forall a. Maybe a
Nothing)
forall build era. TxWithdrawals build era
TxWithdrawalsNone
forall build era. TxCertificates build era
TxCertificatesNone
forall era. TxUpdateProposal era
TxUpdateProposalNone
forall build era. TxMintValue build era
TxMintNone
forall era. TxScriptValidity era
TxScriptValidityNone
case forall era.
IsCardanoEra era =>
TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
createAndValidateTransactionBody TxBodyContent BuildTx ByronEra
txBodyCont of
Left TxBodyError
err -> forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Error occurred while creating a Byron genesis based UTxO transaction: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> [Char]
show TxBodyError
err
Right TxBody ByronEra
txBody -> let bWit :: KeyWitness ByronEra
bWit = SomeByronSigningKey
-> NetworkId -> TxBody ByronEra -> KeyWitness ByronEra
fromByronWitness SomeByronSigningKey
sk NetworkId
nId TxBody ByronEra
txBody
in forall era. [KeyWitness era] -> TxBody era -> Tx era
makeSignedTransaction [KeyWitness ByronEra
bWit] TxBody ByronEra
txBody
where
ByronVerificationKey VerificationKey
vKey = SomeByronSigningKey -> VerificationKey ByronKey
byronWitnessToVerKey SomeByronSigningKey
sk
txIn :: UTxO.TxIn
txIn :: TxIn
txIn = Config -> VerificationKey -> Address -> TxIn
genesisUTxOTxIn Config
gc VerificationKey
vKey Address
bAddr
txSpendUTxOByronPBFT
:: NetworkId
-> SomeByronSigningKey
-> [TxIn]
-> [TxOut CtxTx ByronEra]
-> Tx ByronEra
txSpendUTxOByronPBFT :: NetworkId
-> SomeByronSigningKey
-> [TxIn]
-> [TxOut CtxTx ByronEra]
-> Tx ByronEra
txSpendUTxOByronPBFT NetworkId
nId SomeByronSigningKey
sk [TxIn]
txIns [TxOut CtxTx ByronEra]
outs = do
let txBodyCont :: TxBodyContent BuildTx ByronEra
txBodyCont = forall build era.
TxIns build era
-> TxInsCollateral era
-> TxInsReference build era
-> [TxOut CtxTx era]
-> TxTotalCollateral era
-> TxReturnCollateral CtxTx era
-> TxFee era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
-> TxMetadataInEra era
-> TxAuxScripts era
-> TxExtraKeyWitnesses era
-> BuildTxWith build (Maybe ProtocolParameters)
-> TxWithdrawals build era
-> TxCertificates build era
-> TxUpdateProposal era
-> TxMintValue build era
-> TxScriptValidity era
-> TxBodyContent build era
TxBodyContent
[ ( TxIn
txIn
, forall a. a -> BuildTxWith BuildTx a
BuildTxWith (forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era
KeyWitness KeyWitnessInCtx WitCtxTxIn
KeyWitnessForSpending)
) | TxIn
txIn <- [TxIn]
txIns
]
forall era. TxInsCollateral era
TxInsCollateralNone
forall build era. TxInsReference build era
TxInsReferenceNone
[TxOut CtxTx ByronEra]
outs
forall era. TxTotalCollateral era
TxTotalCollateralNone
forall ctx era. TxReturnCollateral ctx era
TxReturnCollateralNone
(forall era. TxFeesImplicitInEra era -> TxFee era
TxFeeImplicit TxFeesImplicitInEra ByronEra
TxFeesImplicitInByronEra)
( forall era. TxValidityLowerBound era
TxValidityNoLowerBound
, forall era.
ValidityNoUpperBoundSupportedInEra era -> TxValidityUpperBound era
TxValidityNoUpperBound ValidityNoUpperBoundSupportedInEra ByronEra
ValidityNoUpperBoundInByronEra
)
forall era. TxMetadataInEra era
TxMetadataNone
forall era. TxAuxScripts era
TxAuxScriptsNone
forall era. TxExtraKeyWitnesses era
TxExtraKeyWitnessesNone
(forall a. a -> BuildTxWith BuildTx a
BuildTxWith forall a. Maybe a
Nothing)
forall build era. TxWithdrawals build era
TxWithdrawalsNone
forall build era. TxCertificates build era
TxCertificatesNone
forall era. TxUpdateProposal era
TxUpdateProposalNone
forall build era. TxMintValue build era
TxMintNone
forall era. TxScriptValidity era
TxScriptValidityNone
case forall era.
IsCardanoEra era =>
TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
createAndValidateTransactionBody TxBodyContent BuildTx ByronEra
txBodyCont of
Left TxBodyError
err -> forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Error occurred while creating a Byron genesis based UTxO transaction: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> [Char]
show TxBodyError
err
Right TxBody ByronEra
txBody -> let bWit :: KeyWitness ByronEra
bWit = SomeByronSigningKey
-> NetworkId -> TxBody ByronEra -> KeyWitness ByronEra
fromByronWitness SomeByronSigningKey
sk NetworkId
nId TxBody ByronEra
txBody
in forall era. [KeyWitness era] -> TxBody era -> Tx era
makeSignedTransaction [KeyWitness ByronEra
bWit] TxBody ByronEra
txBody
fromByronWitness :: SomeByronSigningKey -> NetworkId -> TxBody ByronEra -> KeyWitness ByronEra
fromByronWitness :: SomeByronSigningKey
-> NetworkId -> TxBody ByronEra -> KeyWitness ByronEra
fromByronWitness SomeByronSigningKey
bw NetworkId
nId TxBody ByronEra
txBody =
case SomeByronSigningKey
bw of
AByronSigningKeyLegacy SigningKey ByronKeyLegacy
sk -> forall key.
IsByronKey key =>
NetworkId
-> TxBody ByronEra -> SigningKey key -> KeyWitness ByronEra
makeByronKeyWitness NetworkId
nId TxBody ByronEra
txBody SigningKey ByronKeyLegacy
sk
AByronSigningKey SigningKey ByronKey
sk' -> forall key.
IsByronKey key =>
NetworkId
-> TxBody ByronEra -> SigningKey key -> KeyWitness ByronEra
makeByronKeyWitness NetworkId
nId TxBody ByronEra
txBody SigningKey ByronKey
sk'
nodeSubmitTx
:: NetworkId
-> GenTx ByronBlock
-> ExceptT ByronTxError IO ()
nodeSubmitTx :: NetworkId -> GenTx ByronBlock -> ExceptT ByronTxError IO ()
nodeSubmitTx NetworkId
network GenTx ByronBlock
gentx = do
SocketPath [Char]
socketPath <- forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT EnvSocketError -> ByronTxError
EnvSocketError forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT IO (Either EnvSocketError SocketPath)
readEnvSocketPath
let connctInfo :: LocalNodeConnectInfo CardanoMode
connctInfo =
LocalNodeConnectInfo {
localNodeSocketPath :: [Char]
localNodeSocketPath = [Char]
socketPath,
localNodeNetworkId :: NetworkId
localNodeNetworkId = NetworkId
network,
localConsensusModeParams :: ConsensusModeParams CardanoMode
localConsensusModeParams = EpochSlots -> ConsensusModeParams CardanoMode
CardanoModeParams (Word64 -> EpochSlots
EpochSlots Word64
21600)
}
SubmitResult (TxValidationErrorInMode CardanoMode)
res <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall mode.
LocalNodeConnectInfo mode
-> TxInMode mode
-> IO (SubmitResult (TxValidationErrorInMode mode))
submitTxToNodeLocal LocalNodeConnectInfo CardanoMode
connctInfo (forall mode.
GenTx ByronBlock -> EraInMode ByronEra mode -> TxInMode mode
TxInByronSpecial GenTx ByronBlock
gentx EraInMode ByronEra CardanoMode
ByronEraInCardanoMode)
case SubmitResult (TxValidationErrorInMode CardanoMode)
res of
SubmitResult (TxValidationErrorInMode CardanoMode)
Net.Tx.SubmitSuccess -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Text -> IO ()
Text.putStrLn Text
"Transaction successfully submitted."
Net.Tx.SubmitFail TxValidationErrorInMode CardanoMode
reason ->
case TxValidationErrorInMode CardanoMode
reason of
TxValidationErrorInMode TxValidationError era
err EraInMode era CardanoMode
_eraInMode -> forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByronTxError
ByronTxSubmitError forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
Text.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> [Char]
show TxValidationError era
err
TxValidationEraMismatch EraMismatch
mismatchErr -> forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left forall a b. (a -> b) -> a -> b
$ EraMismatch -> ByronTxError
ByronTxSubmitErrorEraMismatch EraMismatch
mismatchErr
forall (m :: * -> *) a. Monad m => a -> m a
return ()
fromCborTxAux :: LB.ByteString -> Either Binary.DecoderError (UTxO.ATxAux B.ByteString)
fromCborTxAux :: ByteString -> Either DecoderError (ATxAux ByteString)
fromCborTxAux ByteString
lbs =
forall (f :: * -> *).
Functor f =>
ByteString -> f ByteSpan -> f ByteString
annotationBytes ByteString
lbs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
Text
-> (forall s. Decoder s a) -> ByteString -> Either DecoderError a
Binary.decodeFullDecoder Text
"Cardano.Chain.UTxO.TxAux.fromCborTxAux"
forall a s. FromCBOR a => Decoder s a
Binary.fromCBOR ByteString
lbs
where
annotationBytes :: Functor f => LB.ByteString -> f Binary.ByteSpan -> f B.ByteString
annotationBytes :: forall (f :: * -> *).
Functor f =>
ByteString -> f ByteSpan -> f ByteString
annotationBytes ByteString
bytes = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> ByteString
LB.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteSpan -> ByteString
Binary.slice ByteString
bytes)
toCborTxAux :: UTxO.ATxAux ByteString -> LB.ByteString
toCborTxAux :: ATxAux ByteString -> ByteString
toCborTxAux = ByteString -> ByteString
LB.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ATxAux a -> a
UTxO.aTaAnnotation