From 258928d74ccd6fa80e06dd1de924d2bd1777e185 Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:39:43 -0400 Subject: [PATCH 01/11] Remove ByronTx data constructor --- cardano-api/internal/Cardano/Api/Tx.hs | 77 ++++++++------------------ 1 file changed, 24 insertions(+), 53 deletions(-) diff --git a/cardano-api/internal/Cardano/Api/Tx.hs b/cardano-api/internal/Cardano/Api/Tx.hs index 3b2888b646..cea059df7a 100644 --- a/cardano-api/internal/Cardano/Api/Tx.hs +++ b/cardano-api/internal/Cardano/Api/Tx.hs @@ -1,5 +1,4 @@ {-# LANGUAGE DataKinds #-} -{-# LANGUAGE EmptyCase #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} @@ -24,9 +23,11 @@ module Cardano.Api.Tx ( -- * Signing transactions -- | Creating transaction witnesses one by one, or all in one go. Tx(.., Tx), + Byron.ATxAux(..), getTxBody, getByronTxBody, getTxWitnesses, + getTxWitnessesByron, ScriptValidity(..), -- ** Signing in one go @@ -56,7 +57,6 @@ module Cardano.Api.Tx ( import Cardano.Api.Address import Cardano.Api.Certificate -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ShelleyBasedEra import Cardano.Api.Eras import Cardano.Api.HasTypeProxy @@ -103,16 +103,10 @@ import Lens.Micro -- data Tx era where - - ByronTx - :: ByronEraOnly era - -> Byron.ATxAux ByteString - -> Tx era - - ShelleyTx - :: ShelleyBasedEra era - -> L.Tx (ShelleyLedgerEra era) - -> Tx era + ShelleyTx + :: ShelleyBasedEra era + -> L.Tx (ShelleyLedgerEra era) + -> Tx era instance Show (InAnyCardanoEra Tx) where @@ -136,23 +130,12 @@ instance Eq (InAnyShelleyBasedEra Tx) where -- The GADT in the ShelleyTx case requires a custom instance instance Eq (Tx era) where - (==) (ByronTx _ txA) - (ByronTx _ txB) = txA == txB - (==) (ShelleyTx sbe txA) (ShelleyTx _ txB) = shelleyBasedEraConstraints sbe $ txA == txB - (==) (ByronTx ByronEraOnlyByron _) (ShelleyTx sbe _) = case sbe of {} - (==) (ShelleyTx sbe _) (ByronTx ByronEraOnlyByron _) = case sbe of {} - -- The GADT in the ShelleyTx case requires a custom instance instance Show (Tx era) where - showsPrec p (ByronTx _ tx) = - showParen (p >= 11) $ - showString "ByronTx ByronEraOnlyByron " - . showsPrec 11 tx - showsPrec p (ShelleyTx ShelleyBasedEraShelley tx) = showParen (p >= 11) $ showString "ShelleyTx ShelleyBasedEraShelley " @@ -209,20 +192,13 @@ pattern AsAlonzoTx :: AsType (Tx AlonzoEra) pattern AsAlonzoTx = AsTx AsAlonzoEra {-# COMPLETE AsAlonzoTx #-} -instance IsCardanoEra era => SerialiseAsCBOR (Tx era) where - serialiseToCBOR (ByronTx _ tx) = CBOR.recoverBytes tx - +instance IsShelleyBasedEra era => SerialiseAsCBOR (Tx era) where serialiseToCBOR (ShelleyTx sbe tx) = shelleyBasedEraConstraints sbe $ serialiseShelleyBasedTx tx deserialiseFromCBOR _ bs = - caseByronOrShelleyBasedEra - (\w -> ByronTx w <$> - CBOR.decodeFullAnnotatedBytes - CBOR.byronProtVer "Byron Tx" CBOR.decCBOR (LBS.fromStrict bs) - ) - (\sbe -> deserialiseShelleyBasedTx (ShelleyTx sbe) bs) - (cardanoEra :: CardanoEra era) + shelleyBasedEraConstraints (shelleyBasedEra :: ShelleyBasedEra era) + $ deserialiseShelleyBasedTx (ShelleyTx shelleyBasedEra) bs -- | The serialisation format for the different Shelley-based eras are not the -- same, but they can be handled generally with one overloaded implementation. @@ -243,16 +219,15 @@ deserialiseShelleyBasedTx mkTx bs = (L.eraProtVerLow @ledgerera) "Shelley Tx" CBOR.decCBOR (LBS.fromStrict bs) -instance IsCardanoEra era => HasTextEnvelope (Tx era) where +instance IsShelleyBasedEra era => HasTextEnvelope (Tx era) where textEnvelopeType _ = - case cardanoEra :: CardanoEra era of - ByronEra -> "TxSignedByron" - ShelleyEra -> "TxSignedShelley" - AllegraEra -> "Tx AllegraEra" - MaryEra -> "Tx MaryEra" - AlonzoEra -> "Tx AlonzoEra" - BabbageEra -> "Tx BabbageEra" - ConwayEra -> "Tx ConwayEra" + case shelleyBasedEra :: ShelleyBasedEra era of + ShelleyBasedEraShelley -> "TxSignedShelley" + ShelleyBasedEraAllegra -> "Tx AllegraEra" + ShelleyBasedEraMary -> "Tx MaryEra" + ShelleyBasedEraAlonzo -> "Tx AlonzoEra" + ShelleyBasedEraBabbage -> "Tx BabbageEra" + ShelleyBasedEraConway -> "Tx ConwayEra" data KeyWitness era where @@ -445,17 +420,13 @@ pattern Tx txbody ws <- (getTxBodyAndWitnesses -> (txbody, ws)) getTxBodyAndWitnesses :: Tx era -> (TxBody era, [KeyWitness era]) getTxBodyAndWitnesses tx = (getTxBody tx, getTxWitnesses tx) -getByronTxBody :: Tx ByronEra -> Annotated Byron.Tx ByteString -getByronTxBody (ByronTx _eon Byron.ATxAux { Byron.aTaTx = txbody }) = txbody -getByronTxBody (ShelleyTx sbe _) = case sbe :: ShelleyBasedEra ByronEra of {} +getByronTxBody :: Byron.ATxAux ByteString -> Annotated Byron.Tx ByteString +getByronTxBody (Byron.ATxAux { Byron.aTaTx = txbody }) = txbody -- NB: This is called in getTxBodyAndWitnesses which is fine as -- getTxBodyAndWitnesses is only called in the context of a -- shelley based era anyways. ByronTx will eventually be removed. getTxBody :: Tx era -> TxBody era -getTxBody (ByronTx _eon Byron.ATxAux { Byron.aTaTx = _txbody }) = - error "getTxBody: Use getByronTxBody instead" - getTxBody (ShelleyTx sbe tx) = caseShelleyToMaryOrAlonzoEraOnwards ( const $ @@ -483,14 +454,14 @@ getTxBody (ShelleyTx sbe tx) = ) sbe - -getTxWitnesses :: forall era. Tx era -> [KeyWitness era] -getTxWitnesses (ByronTx ByronEraOnlyByron Byron.ATxAux { Byron.aTaWitness = witnesses }) = +getTxWitnessesByron :: Byron.ATxAux ByteString -> [KeyWitness ByronEra] +getTxWitnessesByron (Byron.ATxAux { Byron.aTaWitness = witnesses }) = map ByronKeyWitness . Vector.toList . unAnnotated $ witnesses +getTxWitnesses :: forall era. Tx era -> [KeyWitness era] getTxWitnesses (ShelleyTx sbe tx') = caseShelleyToMaryOrAlonzoEraOnwards (const (getShelleyTxWitnesses tx')) @@ -856,9 +827,9 @@ makeShelleySignature tosign (ShelleyExtendedSigningKey sk) = signByronTransaction :: NetworkId -> Annotated Byron.Tx ByteString -> [SigningKey ByronKey] - -> Tx ByronEra + -> Byron.ATxAux ByteString signByronTransaction nw txbody sks = - ByronTx ByronEraOnlyByron $ makeSignedByronTransaction witnesses txbody + makeSignedByronTransaction witnesses txbody where witnesses = map (makeByronKeyWitness nw txbody) sks From fb96f16ad5b6ca1ae000f461f7c393a19c2e476e Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:40:18 -0400 Subject: [PATCH 02/11] Implement serializeByronTx and writeByronTxFileTextEnvelopeCddl as we now handle Byron transaction serialization separately --- .../Cardano/Api/SerialiseLedgerCddl.hs | 54 +++++++++++++------ 1 file changed, 37 insertions(+), 17 deletions(-) diff --git a/cardano-api/internal/Cardano/Api/SerialiseLedgerCddl.hs b/cardano-api/internal/Cardano/Api/SerialiseLedgerCddl.hs index a9b3ce68cd..b4c6341cad 100644 --- a/cardano-api/internal/Cardano/Api/SerialiseLedgerCddl.hs +++ b/cardano-api/internal/Cardano/Api/SerialiseLedgerCddl.hs @@ -29,12 +29,14 @@ module Cardano.Api.SerialiseLedgerCddl , deserialiseByronTxCddl , serialiseWitnessLedgerCddl , deserialiseWitnessLedgerCddl + + -- * Byron tx serialization + , serializeByronTx + , writeByronTxFileTextEnvelopeCddl ) where -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ShelleyBasedEra -import Cardano.Api.Eras import Cardano.Api.Error import Cardano.Api.HasTypeProxy import Cardano.Api.IO @@ -43,6 +45,7 @@ import Cardano.Api.SerialiseCBOR import Cardano.Api.Tx import Cardano.Api.Utils +import qualified Cardano.Chain.UTxO as Byron import Cardano.Ledger.Binary (DecoderError) import qualified Cardano.Ledger.Binary as CBOR @@ -51,7 +54,7 @@ import Control.Monad.Trans.Except.Extra (firstExceptT, handleIOExceptT import Data.Aeson import qualified Data.Aeson as Aeson import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', keyOrder) -import Data.Bifunctor (bimap, first) +import Data.Bifunctor (first) import Data.ByteString (ByteString) import qualified Data.ByteString.Base16 as Base16 import qualified Data.ByteString.Lazy as LBS @@ -131,9 +134,9 @@ instance Error TextEnvelopeCddlError where TextEnvelopeCddlErrByronKeyWitnessUnsupported -> "TextEnvelopeCddl error: Byron key witnesses are currently unsupported." -serialiseTxLedgerCddl :: CardanoEra era -> Tx era -> TextEnvelopeCddl +serialiseTxLedgerCddl :: ShelleyBasedEra era -> Tx era -> TextEnvelopeCddl serialiseTxLedgerCddl era tx = - cardanoEraConstraints era $ + shelleyBasedEraConstraints era $ TextEnvelopeCddl { teCddlType = genType tx , teCddlDescription = "Ledger Cddl Format" @@ -148,13 +151,12 @@ serialiseTxLedgerCddl era tx = genTxType :: Text genTxType = case era of - ByronEra -> "Tx ByronEra" - ShelleyEra -> "Tx ShelleyEra" - AllegraEra -> "Tx AllegraEra" - MaryEra -> "Tx MaryEra" - AlonzoEra -> "Tx AlonzoEra" - BabbageEra -> "Tx BabbageEra" - ConwayEra -> "Tx ConwayEra" + ShelleyBasedEraShelley -> "Tx ShelleyEra" + ShelleyBasedEraAllegra -> "Tx AllegraEra" + ShelleyBasedEraMary -> "Tx MaryEra" + ShelleyBasedEraAlonzo -> "Tx AlonzoEra" + ShelleyBasedEraBabbage -> "Tx BabbageEra" + ShelleyBasedEraConway -> "Tx ConwayEra" deserialiseTxLedgerCddl :: () => ShelleyBasedEra era @@ -163,10 +165,28 @@ deserialiseTxLedgerCddl :: () deserialiseTxLedgerCddl era tec = first TextEnvelopeCddlErrCBORDecodingError . deserialiseTx era $ teCddlRawCBOR tec -deserialiseByronTxCddl :: TextEnvelopeCddl -> Either TextEnvelopeCddlError (Tx ByronEra) +writeByronTxFileTextEnvelopeCddl + :: File content Out + -> Byron.ATxAux ByteString + -> IO (Either (FileError ()) ()) +writeByronTxFileTextEnvelopeCddl path w = + runExceptT $ do + handleIOExceptT (FileIOError (unFile path)) $ LBS.writeFile (unFile path) txJson + where + txJson = encodePretty' textEnvelopeCddlJSONConfig (serializeByronTx w) <> "\n" + +serializeByronTx :: Byron.ATxAux ByteString -> TextEnvelopeCddl +serializeByronTx tx = + TextEnvelopeCddl + { teCddlType = "Tx ByronEra" + , teCddlDescription = "Ledger Cddl Format" + , teCddlRawCBOR = CBOR.recoverBytes tx + } + +deserialiseByronTxCddl :: TextEnvelopeCddl -> Either TextEnvelopeCddlError (Byron.ATxAux ByteString) deserialiseByronTxCddl tec = - bimap TextEnvelopeCddlErrCBORDecodingError (ByronTx ByronEraOnlyByron) - $ CBOR.decodeFullAnnotatedBytes + first TextEnvelopeCddlErrCBORDecodingError $ + CBOR.decodeFullAnnotatedBytes CBOR.byronProtVer "Byron Tx" CBOR.decCBOR (LBS.fromStrict $ teCddlRawCBOR tec) @@ -175,7 +195,7 @@ deserialiseTx :: () -> ByteString -> Either DecoderError (Tx era) deserialiseTx sbe = - cardanoEraConstraints (toCardanoEra sbe) + shelleyBasedEraConstraints sbe $ deserialiseFromCBOR (AsTx (proxyToAsType Proxy)) serialiseWitnessLedgerCddl :: forall era. ShelleyBasedEra era -> KeyWitness era -> TextEnvelopeCddl @@ -226,7 +246,7 @@ deserialiseWitnessLedgerCddl sbe TextEnvelopeCddl{teCddlRawCBOR,teCddlDescriptio _ -> Left TextEnvelopeCddlUnknownKeyWitness writeTxFileTextEnvelopeCddl :: () - => CardanoEra era + => ShelleyBasedEra era -> File content Out -> Tx era -> IO (Either (FileError ()) ()) From 20e0428ce04b40248ad81f1cdf2073a30c4cffad Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:44:25 -0400 Subject: [PATCH 03/11] Parameterize TxInMode on ShelleyBasedEra as Byron transactions are only submitted with TxInByronSpecial --- cardano-api/internal/Cardano/Api/IPC.hs | 7 +--- cardano-api/internal/Cardano/Api/InMode.hs | 48 +++++++++------------- 2 files changed, 21 insertions(+), 34 deletions(-) diff --git a/cardano-api/internal/Cardano/Api/IPC.hs b/cardano-api/internal/Cardano/Api/IPC.hs index 043511dbc7..6695c6a4a4 100644 --- a/cardano-api/internal/Cardano/Api/IPC.hs +++ b/cardano-api/internal/Cardano/Api/IPC.hs @@ -77,7 +77,6 @@ module Cardano.Api.IPC ( ) where import Cardano.Api.Block -import Cardano.Api.Eras import Cardano.Api.HasTypeProxy import Cardano.Api.InMode import Cardano.Api.IO @@ -631,11 +630,7 @@ instance ToJSON LocalTxMonitoringResult where ] where txId = case txInMode of - Just (TxInMode e tx) -> - case e of - -- NB: Local tx protocol is not possible in the Byron era - ByronEra -> error "ToJSON LocalTxMonitoringResult: Byron era not supported" - _ -> Just $ getTxId $ getTxBody tx + Just (TxInMode _ tx) -> Just $ getTxId $ getTxBody tx -- TODO: support fetching the ID of a Byron Era transaction _ -> Nothing LocalTxMonitoringMempoolSizeAndCapacity mempool slot -> diff --git a/cardano-api/internal/Cardano/Api/InMode.hs b/cardano-api/internal/Cardano/Api/InMode.hs index c8a640cc84..a1f690aa99 100644 --- a/cardano-api/internal/Cardano/Api/InMode.hs +++ b/cardano-api/internal/Cardano/Api/InMode.hs @@ -27,7 +27,6 @@ module Cardano.Api.InMode ( fromConsensusApplyTxErr, ) where -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ShelleyBasedEra import Cardano.Api.Eras import Cardano.Api.Modes @@ -62,16 +61,16 @@ import GHC.Generics -- LocalTxSubmission protocol. -- data TxInMode where - -- | Everything we consider a normal transaction. + -- | Shelley based transations. -- TxInMode - :: CardanoEra era + :: ShelleyBasedEra era -> Tx era -> TxInMode - -- | Byron has various things we can post to the chain which are not - -- actually transactions. This covers: update proposals, votes and - -- delegation certs. + -- | Legacy Byron transactions. Byron has various things we can + -- post to the chain which are not actually transactions. + -- This covers: update proposals, votes and delegation certs. -- TxInByronSpecial :: Consensus.GenTx Consensus.ByronBlock @@ -88,70 +87,63 @@ fromConsensusGenTx = \case TxInByronSpecial tx' Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (Z tx'))) -> let Consensus.ShelleyTx _txid shelleyEraTx = tx' - in TxInMode ShelleyEra (ShelleyTx ShelleyBasedEraShelley shelleyEraTx) + in TxInMode ShelleyBasedEraShelley (ShelleyTx ShelleyBasedEraShelley shelleyEraTx) Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (Z tx')))) -> let Consensus.ShelleyTx _txid shelleyEraTx = tx' - in TxInMode AllegraEra (ShelleyTx ShelleyBasedEraAllegra shelleyEraTx) + in TxInMode ShelleyBasedEraAllegra (ShelleyTx ShelleyBasedEraAllegra shelleyEraTx) Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (Z tx'))))) -> let Consensus.ShelleyTx _txid shelleyEraTx = tx' - in TxInMode MaryEra (ShelleyTx ShelleyBasedEraMary shelleyEraTx) + in TxInMode ShelleyBasedEraMary (ShelleyTx ShelleyBasedEraMary shelleyEraTx) Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (S (Z tx')))))) -> let Consensus.ShelleyTx _txid shelleyEraTx = tx' - in TxInMode AlonzoEra (ShelleyTx ShelleyBasedEraAlonzo shelleyEraTx) + in TxInMode ShelleyBasedEraAlonzo (ShelleyTx ShelleyBasedEraAlonzo shelleyEraTx) Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (S (S (Z tx'))))))) -> let Consensus.ShelleyTx _txid shelleyEraTx = tx' - in TxInMode BabbageEra (ShelleyTx ShelleyBasedEraBabbage shelleyEraTx) + in TxInMode ShelleyBasedEraBabbage (ShelleyTx ShelleyBasedEraBabbage shelleyEraTx) Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (S (S (S (Z tx')))))))) -> let Consensus.ShelleyTx _txid shelleyEraTx = tx' - in TxInMode ConwayEra (ShelleyTx ShelleyBasedEraConway shelleyEraTx) + in TxInMode ShelleyBasedEraConway (ShelleyTx ShelleyBasedEraConway shelleyEraTx) + + +-- mkByronTx = Consensus.ByronTx (Consensus.byronIdTx tx) tx toConsensusGenTx :: () => Consensus.CardanoBlock L.StandardCrypto ~ block => TxInMode -> Consensus.GenTx block -toConsensusGenTx (TxInMode w (ByronTx ByronEraOnlyByron tx)) = - case w of - ByronEra -> Consensus.HardForkGenTx (Consensus.OneEraGenTx (Z tx')) - where - tx' = Consensus.ByronTx (Consensus.byronIdTx tx) tx - --TODO: add the above as mkByronTx to the consensus code, - -- matching mkShelleyTx below - toConsensusGenTx (TxInByronSpecial gtx) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (Z gtx)) -toConsensusGenTx (TxInMode ShelleyEra (ShelleyTx _ tx)) = +toConsensusGenTx (TxInMode ShelleyBasedEraShelley (ShelleyTx _ tx)) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (Z tx'))) where tx' = Consensus.mkShelleyTx tx -toConsensusGenTx (TxInMode AllegraEra (ShelleyTx _ tx)) = +toConsensusGenTx (TxInMode ShelleyBasedEraAllegra (ShelleyTx _ tx)) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (Z tx')))) where tx' = Consensus.mkShelleyTx tx -toConsensusGenTx (TxInMode MaryEra (ShelleyTx _ tx)) = +toConsensusGenTx (TxInMode ShelleyBasedEraMary (ShelleyTx _ tx)) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (Z tx'))))) where tx' = Consensus.mkShelleyTx tx -toConsensusGenTx (TxInMode AlonzoEra (ShelleyTx _ tx)) = +toConsensusGenTx (TxInMode ShelleyBasedEraAlonzo (ShelleyTx _ tx)) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (S (Z tx')))))) where tx' = Consensus.mkShelleyTx tx -toConsensusGenTx (TxInMode BabbageEra (ShelleyTx _ tx)) = +toConsensusGenTx (TxInMode ShelleyBasedEraBabbage (ShelleyTx _ tx)) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (S (S (Z tx'))))))) where tx' = Consensus.mkShelleyTx tx -toConsensusGenTx (TxInMode ConwayEra (ShelleyTx _ tx)) = +toConsensusGenTx (TxInMode ShelleyBasedEraConway (ShelleyTx _ tx)) = Consensus.HardForkGenTx (Consensus.OneEraGenTx (S (S (S (S (S (S (Z tx')))))))) where tx' = Consensus.mkShelleyTx tx -toConsensusGenTx (TxInMode ByronEra (ShelleyTx _ _)) = - error "Cardano.Api.InMode.toConsensusGenTx: ShelleyTx In Byron era" -- ---------------------------------------------------------------------------- -- Transaction ids in the context of a consensus mode From f0cba13442a12124aa238a2b959e9df0449131c5 Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:46:19 -0400 Subject: [PATCH 04/11] Propagate removal of ByronTx in cardano-api --- cardano-api/internal/Cardano/Api/Fees.hs | 15 --------------- 1 file changed, 15 deletions(-) diff --git a/cardano-api/internal/Cardano/Api/Fees.hs b/cardano-api/internal/Cardano/Api/Fees.hs index 6cae0341b1..8ffdb9c07e 100644 --- a/cardano-api/internal/Cardano/Api/Fees.hs +++ b/cardano-api/internal/Cardano/Api/Fees.hs @@ -46,7 +46,6 @@ module Cardano.Api.Fees ( import Cardano.Api.Address import Cardano.Api.Certificate import Cardano.Api.Eon.BabbageEraOnwards -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.MaryEraOnwards import Cardano.Api.Eon.ShelleyBasedEra import Cardano.Api.Eras.Case @@ -118,9 +117,6 @@ transactionFee sbe txFeeFixed txFeePerByte tx = case tx of ShelleyTx _ tx' -> let x = shelleyBasedEraConstraints sbe $ tx' ^. L.sizeTxF in Lovelace (a * x + b) - --TODO: This can be made to work for Byron txs too. - ByronTx ByronEraOnlyByron _ -> case sbe of {} - {-# DEPRECATED transactionFee "Use 'evaluateTransactionFee' instead" #-} --TODO: in the Byron case the per-byte is non-integral, would need different @@ -146,9 +142,6 @@ estimateTransactionFee :: () -> Int -- ^ The number of extra Byron key witnesses -> Lovelace estimateTransactionFee sbe nw txFeeFixed txFeePerByte = \case - -- TODO: This can be made to work for Byron txs too. - ByronTx ByronEraOnlyByron _ -> - case sbe of {} ShelleyTx era tx -> let Lovelace baseFee = transactionFee sbe txFeeFixed txFeePerByte (ShelleyTx era tx) in \nInputs nOutputs nShelleyKeyWitnesses nByronKeyWitnesses -> @@ -217,7 +210,6 @@ evaluateTransactionFee _ _ _ _ byronwitcount | byronwitcount > 0 = evaluateTransactionFee sbe pp txbody keywitcount _byronwitcount = shelleyBasedEraConstraints sbe $ case makeSignedTransaction' (shelleyBasedToCardanoEra sbe) [] txbody of - ByronTx w _ -> disjointByronEraOnlyAndShelleyBasedEra w sbe ShelleyTx _ tx -> fromShelleyLovelace $ Ledger.evaluateTransactionFee pp tx keywitcount -- | Give an approximate count of the number of key witnesses (i.e. signatures) @@ -478,14 +470,7 @@ evaluateTransactionExecutionUnits :: forall era. () (Map ScriptWitnessIndex (Either ScriptExecutionError ExecutionUnits)) evaluateTransactionExecutionUnits era systemstart epochInfo pp utxo txbody = case makeSignedTransaction' era [] txbody of - ByronTx {} -> evalPreAlonzo ShelleyTx sbe tx' -> evaluateTransactionExecutionUnitsShelley sbe systemstart epochInfo pp utxo tx' - where - -- | Pre-Alonzo eras do not support languages with execution unit accounting. - evalPreAlonzo :: Either TransactionValidityError - (Map ScriptWitnessIndex - (Either ScriptExecutionError ExecutionUnits)) - evalPreAlonzo = Right Map.empty evaluateTransactionExecutionUnitsShelley :: forall era. () => ShelleyBasedEra era From d0c5fd661e7c0371f56e3184352e79fe076022ad Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:52:07 -0400 Subject: [PATCH 05/11] Remove support for Byron blocks in fold blocks --- cardano-api/internal/Cardano/Api/Block.hs | 16 ++++------------ 1 file changed, 4 insertions(+), 12 deletions(-) diff --git a/cardano-api/internal/Cardano/Api/Block.hs b/cardano-api/internal/Cardano/Api/Block.hs index 0b39791a91..2c491c719e 100644 --- a/cardano-api/internal/Cardano/Api/Block.hs +++ b/cardano-api/internal/Cardano/Api/Block.hs @@ -49,7 +49,6 @@ module Cardano.Api.Block ( makeChainTip, ) where -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ShelleyBasedEra import Cardano.Api.Eras import Cardano.Api.Hash @@ -60,8 +59,6 @@ import Cardano.Api.SerialiseRaw import Cardano.Api.SerialiseUsing import Cardano.Api.Tx -import qualified Cardano.Chain.Block as Byron -import qualified Cardano.Chain.UTxO as Byron import qualified Cardano.Crypto.Hash.Class as Crypto import qualified Cardano.Crypto.Hashing import qualified Cardano.Ledger.Api as L @@ -159,15 +156,10 @@ instance Show (Block era) where getBlockTxs :: forall era . Block era -> [Tx era] getBlockTxs = \case - ByronBlock Consensus.ByronBlock { Consensus.byronBlockRaw } -> - case byronBlockRaw of - Byron.ABOBBoundary{} -> [] -- no txs in EBBs - Byron.ABOBBlock Byron.ABlock { - Byron.blockBody = - Byron.ABody { - Byron.bodyTxPayload = Byron.ATxPayload txs - } - } -> map (ByronTx ByronEraOnlyByron) txs + -- In the context of foldBlocks we don't care about the Byron era. + -- Testing leans on ledger events which is a Shelley onwards feature. + ByronBlock Consensus.ByronBlock{} -> [] + ShelleyBlock sbe Consensus.ShelleyBlock{Consensus.shelleyBlockRaw} -> shelleyBasedEraConstraints sbe $ getShelleyBlockTxs sbe shelleyBlockRaw From e5ee0bbe9dc21d8b50f3e1831a0b9dee3952272c Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:53:03 -0400 Subject: [PATCH 06/11] Update Cardano.Api.Byron to expose ledger's transaction type for Byron txs (ATxAux) Remove dead code --- cardano-api/internal/Cardano/Api/Eras/Case.hs | 5 ----- cardano-api/src/Cardano/Api/Byron.hs | 9 +++++++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/cardano-api/internal/Cardano/Api/Eras/Case.hs b/cardano-api/internal/Cardano/Api/Eras/Case.hs index 202315da7c..f87f4af604 100644 --- a/cardano-api/internal/Cardano/Api/Eras/Case.hs +++ b/cardano-api/internal/Cardano/Api/Eras/Case.hs @@ -17,7 +17,6 @@ module Cardano.Api.Eras.Case , caseShelleyToBabbageOrConwayEraOnwards -- Proofs - , noByronEraInShelleyBasedEra , disjointByronEraOnlyAndShelleyBasedEra -- Conversions @@ -148,10 +147,6 @@ caseShelleyToBabbageOrConwayEraOnwards l r = \case ShelleyBasedEraBabbage -> l ShelleyToBabbageEraBabbage ShelleyBasedEraConway -> r ConwayEraOnwardsConway -{-# DEPRECATED noByronEraInShelleyBasedEra "Use disjointByronEraOnlyAndShelleyBasedEra instead" #-} -noByronEraInShelleyBasedEra :: ShelleyBasedEra era -> ByronEraOnly era -> a -noByronEraInShelleyBasedEra = flip disjointByronEraOnlyAndShelleyBasedEra - disjointByronEraOnlyAndShelleyBasedEra :: ByronEraOnly era -> ShelleyBasedEra era -> a disjointByronEraOnlyAndShelleyBasedEra ByronEraOnlyByron sbe = case sbe of {} diff --git a/cardano-api/src/Cardano/Api/Byron.hs b/cardano-api/src/Cardano/Api/Byron.hs index 54a2103534..ffede061c3 100644 --- a/cardano-api/src/Cardano/Api/Byron.hs +++ b/cardano-api/src/Cardano/Api/Byron.hs @@ -31,7 +31,7 @@ module Cardano.Api.Byron -- * Signing transactions -- | Creating transaction witnesses one by one, or all in one go. - Tx(ByronTx), + ATxAux(..), -- ** Incremental signing and separate witnesses KeyWitness (ByronKeyWitness), @@ -82,13 +82,18 @@ module Cardano.Api.Byron -- * Hardcoded configuration parameters applicationName, applicationVersion, - softwareVersion + softwareVersion, + + -- * Serialization + serializeByronTx, + writeByronTxFileTextEnvelopeCddl, ) where import Cardano.Api import Cardano.Api.Address import Cardano.Api.Keys.Byron import Cardano.Api.NetworkId +import Cardano.Api.SerialiseLedgerCddl import Cardano.Api.SpecialByron import Cardano.Api.Tx import Cardano.Api.TxBody From ba36bfdc8085e5b7039e8b87b9c8b8dce11c5580 Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 09:53:49 -0400 Subject: [PATCH 07/11] Update tests --- cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs | 17 +++-------------- cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs | 12 ++++++------ .../Test/Cardano/Api/Typed/CBOR.hs | 8 ++++---- 3 files changed, 13 insertions(+), 24 deletions(-) diff --git a/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs b/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs index 69f7d097ed..8a41c3c9f0 100644 --- a/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs +++ b/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs @@ -8,6 +8,7 @@ module Test.Gen.Cardano.Api.Byron import Cardano.Api hiding (txIns) import Cardano.Api.Byron +import qualified Cardano.Api.Byron as Byron import Data.Proxy @@ -20,17 +21,8 @@ import Test.Tasty.Hedgehog prop_byron_roundtrip_txbody_CBOR :: Property prop_byron_roundtrip_txbody_CBOR = property $ do - let byron = ByronEra x <- forAll $ makeSignedByronTransaction [] <$> genTxBodyByron - tripping (ByronTx ByronEraOnlyByron x) (serialiseTxLedgerCddl byron) deserialiseByronTxCddl - - -prop_byron_roundtrip_tx_CBOR :: Property -prop_byron_roundtrip_tx_CBOR = property $ do - let byron = ByronEra - x <- forAll genTxByron - cardanoEraConstraints byron $ trippingCbor (proxyToAsType Proxy) x - + tripping x Byron.serializeByronTx deserialiseByronTxCddl prop_byron_roundtrip_witness_CBOR :: Property prop_byron_roundtrip_witness_CBOR = property $ do @@ -38,17 +30,14 @@ prop_byron_roundtrip_witness_CBOR = property $ do x <- forAll genByronKeyWitness cardanoEraConstraints byron $ trippingCbor (AsKeyWitness (proxyToAsType Proxy)) x - prop_byron_roundtrip_Tx_Cddl :: Property prop_byron_roundtrip_Tx_Cddl = property $ do - let byron = ByronEra x <- forAll genTxByron - tripping x (serialiseTxLedgerCddl byron) deserialiseByronTxCddl + tripping x serializeByronTx deserialiseByronTxCddl tests :: TestTree tests = testGroup "Test.Gen.Cardano.Api.Byron" [ testProperty "Byron roundtrip txbody CBOR" prop_byron_roundtrip_txbody_CBOR - , testProperty "Byron roundtrip tx certificate CBOR" prop_byron_roundtrip_tx_CBOR , testProperty "Byron roundtrip witness CBOR" prop_byron_roundtrip_witness_CBOR , testProperty "Byron roundtrip tx CBOR" prop_byron_roundtrip_Tx_Cddl ] diff --git a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs index 020a100850..0a015f2242 100644 --- a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +++ b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs @@ -134,8 +134,9 @@ module Test.Gen.Cardano.Api.Typed import Cardano.Api hiding (txIns) import qualified Cardano.Api as Api -import Cardano.Api.Byron (KeyWitness (ByronKeyWitness), Tx (ByronTx), +import Cardano.Api.Byron (KeyWitness (ByronKeyWitness), WitnessNetworkIdOrByronAddress (..)) +import qualified Cardano.Api.Byron as Byron import Cardano.Api.Eon.AllegraEraOnwards (allegraEraOnwardsToShelleyBasedEra) import Cardano.Api.Error import qualified Cardano.Api.Ledger as L @@ -718,12 +719,11 @@ genTxFee = genAddressInEraByron :: Gen (AddressInEra ByronEra) genAddressInEraByron = byronAddressInEra <$> genAddressByron -genTxByron :: Gen (Tx ByronEra) +genTxByron :: Gen (Byron.ATxAux ByteString) genTxByron = do - tx <- makeSignedByronTransaction - <$> genWitnessesByron - <*> genTxBodyByron - return $ ByronTx ByronEraOnlyByron tx + makeSignedByronTransaction + <$> genWitnessesByron + <*> genTxBodyByron genTxOutValueByron :: Gen (TxOutValue ByronEra) genTxOutValueByron = TxOutValueByron <$> genPositiveLovelace diff --git a/cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/CBOR.hs b/cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/CBOR.hs index ffca31fba8..61ca2ddda5 100644 --- a/cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/CBOR.hs +++ b/cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/CBOR.hs @@ -31,19 +31,19 @@ prop_roundtrip_txbody_CBOR :: Property prop_roundtrip_txbody_CBOR = H.property $ do AnyShelleyBasedEra era <- H.forAll $ Gen.element [minBound..maxBound] x <- H.forAll $ makeSignedTransaction [] <$> genTxBody era - H.tripping x (serialiseTxLedgerCddl $ toCardanoEra era) (deserialiseTxLedgerCddl era) + H.tripping x (serialiseTxLedgerCddl era) (deserialiseTxLedgerCddl era) prop_roundtrip_tx_CBOR :: Property prop_roundtrip_tx_CBOR = H.property $ do AnyShelleyBasedEra era <- H.forAll $ Gen.element [minBound..maxBound] x <- H.forAll $ genTx era - cardanoEraConstraints (toCardanoEra era) $ H.trippingCbor (proxyToAsType Proxy) x + shelleyBasedEraConstraints era $ H.trippingCbor (proxyToAsType Proxy) x prop_roundtrip_witness_CBOR :: Property prop_roundtrip_witness_CBOR = H.property $ do AnyShelleyBasedEra era <- H.forAll $ Gen.element [minBound..maxBound] x <- H.forAll $ genCardanoKeyWitness era - cardanoEraConstraints (toCardanoEra era) $ H.trippingCbor (AsKeyWitness (proxyToAsType Proxy)) x + shelleyBasedEraConstraints era $ H.trippingCbor (AsKeyWitness (proxyToAsType Proxy)) x prop_roundtrip_operational_certificate_CBOR :: Property prop_roundtrip_operational_certificate_CBOR = H.property $ do @@ -170,7 +170,7 @@ prop_roundtrip_Tx_Cddl :: Property prop_roundtrip_Tx_Cddl = H.property $ do AnyShelleyBasedEra era <- H.forAll $ Gen.element [minBound..maxBound] x <- forAll $ genTx era - H.tripping x (serialiseTxLedgerCddl $ toCardanoEra era) (deserialiseTxLedgerCddl era) + H.tripping x (serialiseTxLedgerCddl era) (deserialiseTxLedgerCddl era) prop_roundtrip_TxWitness_Cddl :: Property prop_roundtrip_TxWitness_Cddl = H.property $ do From fa52f31130715d668689002cdf094f40b462e42a Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Thu, 23 Nov 2023 14:52:38 -0400 Subject: [PATCH 08/11] Remove Byron specific TxFeeImplicit constructor --- cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs | 9 ++-- cardano-api/internal/Cardano/Api/TxBody.hs | 41 ++----------------- cardano-api/src/Cardano/Api.hs | 1 - 3 files changed, 6 insertions(+), 45 deletions(-) diff --git a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs index 0a015f2242..51086443aa 100644 --- a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +++ b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs @@ -644,7 +644,7 @@ genTxBodyContent sbe = do txOuts <- Gen.list (Range.constant 1 10) (genTxOutTxContext sbe) txTotalCollateral <- genTxTotalCollateral era txReturnCollateral <- genTxReturnCollateral sbe - txFee <- genTxFee era + txFee <- genTxFee sbe txValidityLowerBound <- genTxValidityLowerBound era txValidityUpperBound <- genTxValidityUpperBound era txMetadata <- genTxMetadataInEra era @@ -710,11 +710,8 @@ genTxTotalCollateral = (pure TxTotalCollateralNone) (\w -> TxTotalCollateral w <$> genPositiveLovelace) -genTxFee :: CardanoEra era -> Gen (TxFee era) -genTxFee = - caseByronOrShelleyBasedEra - (pure . TxFeeImplicit) - (\w -> TxFeeExplicit w <$> genLovelace) +genTxFee :: ShelleyBasedEra era -> Gen (TxFee era) +genTxFee w = TxFeeExplicit w <$> genLovelace genAddressInEraByron :: Gen (AddressInEra ByronEra) genAddressInEraByron = byronAddressInEra <$> genAddressByron diff --git a/cardano-api/internal/Cardano/Api/TxBody.hs b/cardano-api/internal/Cardano/Api/TxBody.hs index 3023abdb94..ec7c240a65 100644 --- a/cardano-api/internal/Cardano/Api/TxBody.hs +++ b/cardano-api/internal/Cardano/Api/TxBody.hs @@ -151,7 +151,6 @@ module Cardano.Api.TxBody ( -- * Data family instances AsType(AsTxId, AsTxBody, AsByronTxBody, AsShelleyTxBody, AsMaryTxBody), - getByronTxBodyContent, getTxBodyContent, ) where @@ -1031,18 +1030,13 @@ parseHash asType = do -- data TxFee era where - TxFeeImplicit :: ByronEraOnly era -> TxFee era - TxFeeExplicit :: ShelleyBasedEra era -> Lovelace -> TxFee era deriving instance Eq (TxFee era) deriving instance Show (TxFee era) -defaultTxFee :: CardanoEra era -> TxFee era -defaultTxFee = - caseByronOrShelleyBasedEra - TxFeeImplicit - (\w -> TxFeeExplicit w mempty) +defaultTxFee :: ShelleyBasedEra era -> TxFee era +defaultTxFee w = TxFeeExplicit w mempty -- ---------------------------------------------------------------------------- -- Transaction validity range @@ -2408,34 +2402,6 @@ classifyRangeError txout = TxOut (AddressInEra ByronAddressInAnyEra (ByronAddress _)) (TxOutValueShelleyBased w _) _ _ -> case w of {} TxOut (AddressInEra (ShelleyAddressInEra sbe) ShelleyAddress{}) _ _ _ -> case sbe of {} -getByronTxBodyContent :: () - => ByronEraOnly era - -> Annotated Byron.Tx ByteString - -> TxBodyContent ViewTx era -getByronTxBodyContent ByronEraOnlyByron (Annotated Byron.UnsafeTx{txInputs, txOutputs} _) = - TxBodyContent - { txIns = [(fromByronTxIn input, ViewTx) | input <- toList txInputs] - , txInsCollateral = TxInsCollateralNone - , txInsReference = TxInsReferenceNone - , txOuts = fromByronTxOut ByronEraOnlyByron <$> toList txOutputs - , txReturnCollateral = TxReturnCollateralNone - , txTotalCollateral = TxTotalCollateralNone - , txFee = TxFeeImplicit ByronEraOnlyByron - , txValidityLowerBound = TxValidityNoLowerBound - , txValidityUpperBound = TxValidityNoUpperBound ByronEraOnlyByron - , txMetadata = TxMetadataNone - , txAuxScripts = TxAuxScriptsNone - , txExtraKeyWits = TxExtraKeyWitnessesNone - , txProtocolParams = ViewTx - , txWithdrawals = TxWithdrawalsNone - , txCertificates = TxCertificatesNone - , txUpdateProposal = TxUpdateProposalNone - , txMintValue = TxMintNone - , txScriptValidity = TxScriptValidityNone - , txProposalProcedures = Nothing - , txVotingProcedures = Nothing - } - convTxIns :: TxIns BuildTx era -> Set (L.TxIn StandardCrypto) convTxIns txIns = Set.fromList (map (toShelleyTxIn . fst) txIns) @@ -2482,8 +2448,7 @@ convWithdrawals txWithdrawals = TxWithdrawals _ ws -> toShelleyWithdrawal ws convTransactionFee :: ShelleyBasedEra era -> TxFee era -> Ledger.Coin -convTransactionFee sbe = \case - TxFeeImplicit w -> disjointByronEraOnlyAndShelleyBasedEra w sbe +convTransactionFee _ = \case TxFeeExplicit _ fee -> toShelleyLovelace fee convValidityLowerBound :: () diff --git a/cardano-api/src/Cardano/Api.hs b/cardano-api/src/Cardano/Api.hs index 7ee5fa7cde..77cb73d94f 100644 --- a/cardano-api/src/Cardano/Api.hs +++ b/cardano-api/src/Cardano/Api.hs @@ -305,7 +305,6 @@ module Cardano.Api ( createAndValidateTransactionBody, makeByronTransactionBody, TxBodyContent(..), - getByronTxBodyContent, getTxBodyContent, -- ** Transaction body builders From 275f1e6cde778ab274e399b5968d81f8e2fdee63 Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Thu, 23 Nov 2023 14:56:33 -0400 Subject: [PATCH 09/11] Remove Byron specific TxValidityNoUpperBound constructor --- cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs | 11 +++----- cardano-api/internal/Cardano/Api/TxBody.hs | 25 +++---------------- 2 files changed, 7 insertions(+), 29 deletions(-) diff --git a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs index 51086443aa..d536253b02 100644 --- a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +++ b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs @@ -545,14 +545,9 @@ genTxValidityLowerBound = (\w -> TxValidityLowerBound w <$> genTtl) -- TODO: Accept a range for generating ttl. -genTxValidityUpperBound :: CardanoEra era -> Gen (TxValidityUpperBound era) -genTxValidityUpperBound era = - forEraInEon era - ( forEraInEon era - (error "genTxValidityUpperBound: unexpected era support combination") - (pure . TxValidityNoUpperBound) - ) - (\w -> TxValidityUpperBound w <$> Gen.maybe genTtl) +genTxValidityUpperBound :: ShelleyBasedEra era -> Gen (TxValidityUpperBound era) +genTxValidityUpperBound sbe = + TxValidityUpperBound sbe <$> Gen.maybe genTtl genTxMetadataInEra :: CardanoEra era -> Gen (TxMetadataInEra era) genTxMetadataInEra = diff --git a/cardano-api/internal/Cardano/Api/TxBody.hs b/cardano-api/internal/Cardano/Api/TxBody.hs index ec7c240a65..f39a606029 100644 --- a/cardano-api/internal/Cardano/Api/TxBody.hs +++ b/cardano-api/internal/Cardano/Api/TxBody.hs @@ -159,7 +159,6 @@ import Cardano.Api.Certificate import Cardano.Api.Eon.AllegraEraOnwards import Cardano.Api.Eon.AlonzoEraOnwards import Cardano.Api.Eon.BabbageEraOnwards -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ConwayEraOnwards import Cardano.Api.Eon.MaryEraOnwards import Cardano.Api.Eon.ShelleyBasedEra @@ -682,14 +681,6 @@ instance IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) where <*> return (TxOutDatumHash w dHash) <*> return ReferenceScriptNone -fromByronTxOut :: ByronEraOnly era -> Byron.TxOut -> TxOut ctx era -fromByronTxOut ByronEraOnlyByron (Byron.TxOut addr value) = - TxOut - (AddressInEra ByronAddressInAnyEra (ByronAddress addr)) - (TxOutValueByron (fromByronLovelace value)) - TxOutDatumNone ReferenceScriptNone - - toByronTxOut :: TxOut ctx ByronEra -> Maybe Byron.TxOut toByronTxOut = \case TxOut (AddressInEra ByronAddressInAnyEra (ByronAddress addr)) (TxOutValueByron value) _ _ -> @@ -1045,10 +1036,6 @@ defaultTxFee w = TxFeeExplicit w mempty -- | This was formerly known as the TTL. -- data TxValidityUpperBound era where - TxValidityNoUpperBound - :: ByronEraOnly era - -> TxValidityUpperBound era - TxValidityUpperBound :: ShelleyBasedEra era -> Maybe SlotNo @@ -1058,12 +1045,9 @@ deriving instance Eq (TxValidityUpperBound era) deriving instance Show (TxValidityUpperBound era) defaultTxValidityUpperBound :: () - => CardanoEra era + => ShelleyBasedEra era -> TxValidityUpperBound era -defaultTxValidityUpperBound = - caseByronOrShelleyBasedEra - TxValidityNoUpperBound - (\sbe -> TxValidityUpperBound sbe Nothing) +defaultTxValidityUpperBound sbe = TxValidityUpperBound sbe Nothing data TxValidityLowerBound era where @@ -1222,7 +1206,7 @@ data TxBodyContent build era = deriving (Eq, Show) defaultTxBodyContent :: () - => CardanoEra era + => ShelleyBasedEra era -> TxBodyContent BuildTx era defaultTxBodyContent era = TxBodyContent { txIns = [] @@ -2462,8 +2446,7 @@ convValidityUpperBound :: () => ShelleyBasedEra era -> TxValidityUpperBound era -> Maybe SlotNo -convValidityUpperBound sbe = \case - TxValidityNoUpperBound w -> disjointByronEraOnlyAndShelleyBasedEra w sbe +convValidityUpperBound _ = \case TxValidityUpperBound _ ms -> ms -- | Convert transaction update proposal into ledger update proposal From f4f19a3fa42d9b00e2ffb9db7a2af36f137dae92 Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Thu, 23 Nov 2023 14:59:03 -0400 Subject: [PATCH 10/11] Delete Cardano.Api.Eon.ByronEraOnly module --- cardano-api/cardano-api.cabal | 1 - cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs | 2 +- .../internal/Cardano/Api/Eon/ByronEraOnly.hs | 55 ------------------- cardano-api/internal/Cardano/Api/Eras.hs | 2 +- cardano-api/internal/Cardano/Api/Eras/Case.hs | 11 +--- cardano-api/src/Cardano/Api.hs | 5 -- 6 files changed, 4 insertions(+), 72 deletions(-) delete mode 100644 cardano-api/internal/Cardano/Api/Eon/ByronEraOnly.hs diff --git a/cardano-api/cardano-api.cabal b/cardano-api/cardano-api.cabal index c0a6002002..bd4cdecb34 100644 --- a/cardano-api/cardano-api.cabal +++ b/cardano-api/cardano-api.cabal @@ -61,7 +61,6 @@ library internal Cardano.Api.Eon.AllegraEraOnwards Cardano.Api.Eon.AlonzoEraOnwards Cardano.Api.Eon.BabbageEraOnwards - Cardano.Api.Eon.ByronEraOnly Cardano.Api.Eon.ByronToAlonzoEra Cardano.Api.Eon.ConwayEraOnwards Cardano.Api.Eon.MaryEraOnwards diff --git a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs index d536253b02..392740555f 100644 --- a/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +++ b/cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs @@ -641,7 +641,7 @@ genTxBodyContent sbe = do txReturnCollateral <- genTxReturnCollateral sbe txFee <- genTxFee sbe txValidityLowerBound <- genTxValidityLowerBound era - txValidityUpperBound <- genTxValidityUpperBound era + txValidityUpperBound <- genTxValidityUpperBound sbe txMetadata <- genTxMetadataInEra era txAuxScripts <- genTxAuxScripts sbe let txExtraKeyWits = TxExtraKeyWitnessesNone --TODO: Alonzo era: Generate witness key hashes diff --git a/cardano-api/internal/Cardano/Api/Eon/ByronEraOnly.hs b/cardano-api/internal/Cardano/Api/Eon/ByronEraOnly.hs deleted file mode 100644 index 3ec28999a3..0000000000 --- a/cardano-api/internal/Cardano/Api/Eon/ByronEraOnly.hs +++ /dev/null @@ -1,55 +0,0 @@ -{-# LANGUAGE ConstraintKinds #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE TypeFamilies #-} - -module Cardano.Api.Eon.ByronEraOnly - ( ByronEraOnly(..) - , byronEraOnlyConstraints - , byronEraOnlyToCardanoEra - - , ByronEraOnlyConstraints - ) where - -import Cardano.Api.Eras.Core - -import Data.Typeable (Typeable) - -data ByronEraOnly era where - ByronEraOnlyByron :: ByronEraOnly ByronEra - -deriving instance Show (ByronEraOnly era) -deriving instance Eq (ByronEraOnly era) - -instance Eon ByronEraOnly where - inEonForEra no yes = \case - ByronEra -> yes ByronEraOnlyByron - ShelleyEra -> no - AllegraEra -> no - MaryEra -> no - AlonzoEra -> no - BabbageEra -> no - ConwayEra -> no - -instance ToCardanoEra ByronEraOnly where - toCardanoEra = \case - ByronEraOnlyByron -> ByronEra - -type ByronEraOnlyConstraints era = - ( IsCardanoEra era - , Typeable era - ) - -byronEraOnlyConstraints :: () - => ByronEraOnly era - -> (ByronEraOnlyConstraints era => a) - -> a -byronEraOnlyConstraints = \case - ByronEraOnlyByron -> id - -byronEraOnlyToCardanoEra :: ByronEraOnly era -> CardanoEra era -byronEraOnlyToCardanoEra = \case - ByronEraOnlyByron -> ByronEra diff --git a/cardano-api/internal/Cardano/Api/Eras.hs b/cardano-api/internal/Cardano/Api/Eras.hs index b9b8bfabef..0fab2d8115 100644 --- a/cardano-api/internal/Cardano/Api/Eras.hs +++ b/cardano-api/internal/Cardano/Api/Eras.hs @@ -38,7 +38,7 @@ module Cardano.Api.Eras -- * Era case handling - -- ** Case on CardanoEra + -- ** Case on CardanoEra , caseByronOrShelleyBasedEra -- ** Case on ShelleyBasedEra diff --git a/cardano-api/internal/Cardano/Api/Eras/Case.hs b/cardano-api/internal/Cardano/Api/Eras/Case.hs index f87f4af604..501703002a 100644 --- a/cardano-api/internal/Cardano/Api/Eras/Case.hs +++ b/cardano-api/internal/Cardano/Api/Eras/Case.hs @@ -16,9 +16,6 @@ module Cardano.Api.Eras.Case , caseShelleyToAlonzoOrBabbageEraOnwards , caseShelleyToBabbageOrConwayEraOnwards - -- Proofs - , disjointByronEraOnlyAndShelleyBasedEra - -- Conversions , shelleyToAlonzoEraToShelleyToBabbageEra , alonzoEraOnwardsToMaryEraOnwards @@ -29,7 +26,6 @@ module Cardano.Api.Eras.Case import Cardano.Api.Eon.AllegraEraOnwards import Cardano.Api.Eon.AlonzoEraOnwards import Cardano.Api.Eon.BabbageEraOnwards -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ByronToAlonzoEra import Cardano.Api.Eon.ConwayEraOnwards import Cardano.Api.Eon.MaryEraOnwards @@ -43,12 +39,12 @@ import Cardano.Api.Eras.Core -- | @caseByronOrShelleyBasedEra f g era@ applies @f@ to byron and @g@ to other eras. caseByronOrShelleyBasedEra :: () - => (ByronEraOnly era -> a) + => a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a caseByronOrShelleyBasedEra l r = \case - ByronEra -> l ByronEraOnlyByron + ByronEra -> l ShelleyEra -> r ShelleyBasedEraShelley AllegraEra -> r ShelleyBasedEraAllegra MaryEra -> r ShelleyBasedEraMary @@ -147,9 +143,6 @@ caseShelleyToBabbageOrConwayEraOnwards l r = \case ShelleyBasedEraBabbage -> l ShelleyToBabbageEraBabbage ShelleyBasedEraConway -> r ConwayEraOnwardsConway -disjointByronEraOnlyAndShelleyBasedEra :: ByronEraOnly era -> ShelleyBasedEra era -> a -disjointByronEraOnlyAndShelleyBasedEra ByronEraOnlyByron sbe = case sbe of {} - shelleyToAlonzoEraToShelleyToBabbageEra :: () => ShelleyToAlonzoEra era -> ShelleyToBabbageEra era diff --git a/cardano-api/src/Cardano/Api.hs b/cardano-api/src/Cardano/Api.hs index 77cb73d94f..762ee42c71 100644 --- a/cardano-api/src/Cardano/Api.hs +++ b/cardano-api/src/Cardano/Api.hs @@ -55,10 +55,6 @@ module Cardano.Api ( -- ** From Byron - ByronEraOnly(..), - byronEraOnlyConstraints, - byronEraOnlyToCardanoEra, - ByronToAlonzoEra(..), byronToAlonzoEraConstraints, byronToAlonzoEraToCardanoEra, @@ -1001,7 +997,6 @@ import Cardano.Api.DRepMetadata import Cardano.Api.Eon.AllegraEraOnwards import Cardano.Api.Eon.AlonzoEraOnwards import Cardano.Api.Eon.BabbageEraOnwards -import Cardano.Api.Eon.ByronEraOnly import Cardano.Api.Eon.ByronToAlonzoEra import Cardano.Api.Eon.ConwayEraOnwards import Cardano.Api.Eon.MaryEraOnwards From 72cbddffcf0150e503f3e4f10438e86c8590b40e Mon Sep 17 00:00:00 2001 From: Jordan Millar Date: Tue, 28 Nov 2023 08:47:51 -0400 Subject: [PATCH 11/11] Minor clean up --- cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs | 3 +-- cardano-api/internal/Cardano/Api/Eras.hs | 2 +- cardano-api/internal/Cardano/Api/Eras/Case.hs | 8 +++++--- cardano-api/internal/Cardano/Api/InMode.hs | 6 ++---- 4 files changed, 9 insertions(+), 10 deletions(-) diff --git a/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs b/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs index 8a41c3c9f0..6a4e600bab 100644 --- a/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs +++ b/cardano-api/gen/Test/Gen/Cardano/Api/Byron.hs @@ -8,7 +8,6 @@ module Test.Gen.Cardano.Api.Byron import Cardano.Api hiding (txIns) import Cardano.Api.Byron -import qualified Cardano.Api.Byron as Byron import Data.Proxy @@ -22,7 +21,7 @@ import Test.Tasty.Hedgehog prop_byron_roundtrip_txbody_CBOR :: Property prop_byron_roundtrip_txbody_CBOR = property $ do x <- forAll $ makeSignedByronTransaction [] <$> genTxBodyByron - tripping x Byron.serializeByronTx deserialiseByronTxCddl + tripping x serializeByronTx deserialiseByronTxCddl prop_byron_roundtrip_witness_CBOR :: Property prop_byron_roundtrip_witness_CBOR = property $ do diff --git a/cardano-api/internal/Cardano/Api/Eras.hs b/cardano-api/internal/Cardano/Api/Eras.hs index 0fab2d8115..b9b8bfabef 100644 --- a/cardano-api/internal/Cardano/Api/Eras.hs +++ b/cardano-api/internal/Cardano/Api/Eras.hs @@ -38,7 +38,7 @@ module Cardano.Api.Eras -- * Era case handling - -- ** Case on CardanoEra + -- ** Case on CardanoEra , caseByronOrShelleyBasedEra -- ** Case on ShelleyBasedEra diff --git a/cardano-api/internal/Cardano/Api/Eras/Case.hs b/cardano-api/internal/Cardano/Api/Eras/Case.hs index 501703002a..d9746af1a3 100644 --- a/cardano-api/internal/Cardano/Api/Eras/Case.hs +++ b/cardano-api/internal/Cardano/Api/Eras/Case.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE EmptyCase #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} @@ -37,14 +36,17 @@ import Cardano.Api.Eon.ShelleyToBabbageEra import Cardano.Api.Eon.ShelleyToMaryEra import Cardano.Api.Eras.Core --- | @caseByronOrShelleyBasedEra f g era@ applies @f@ to byron and @g@ to other eras. +-- | @caseByronOrShelleyBasedEra f g era@ returns @f@ in Byron and applies @g@ to Shelley-based eras. caseByronOrShelleyBasedEra :: () => a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a caseByronOrShelleyBasedEra l r = \case - ByronEra -> l + ByronEra -> l -- We no longer provide the witness because Byron is isolated. + -- This function will be deleted shortly after build-raw --byron-era is + -- deprecated in cardano-cli + ShelleyEra -> r ShelleyBasedEraShelley AllegraEra -> r ShelleyBasedEraAllegra MaryEra -> r ShelleyBasedEraMary diff --git a/cardano-api/internal/Cardano/Api/InMode.hs b/cardano-api/internal/Cardano/Api/InMode.hs index a1f690aa99..40630a41e0 100644 --- a/cardano-api/internal/Cardano/Api/InMode.hs +++ b/cardano-api/internal/Cardano/Api/InMode.hs @@ -61,14 +61,14 @@ import GHC.Generics -- LocalTxSubmission protocol. -- data TxInMode where - -- | Shelley based transations. + -- | Shelley based transactions. -- TxInMode :: ShelleyBasedEra era -> Tx era -> TxInMode - -- | Legacy Byron transactions. Byron has various things we can + -- | Legacy Byron transactions and things we can -- post to the chain which are not actually transactions. -- This covers: update proposals, votes and delegation certs. -- @@ -105,8 +105,6 @@ fromConsensusGenTx = \case in TxInMode ShelleyBasedEraConway (ShelleyTx ShelleyBasedEraConway shelleyEraTx) --- mkByronTx = Consensus.ByronTx (Consensus.byronIdTx tx) tx - toConsensusGenTx :: () => Consensus.CardanoBlock L.StandardCrypto ~ block => TxInMode