Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
9 changes: 4 additions & 5 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,9 @@ repository cardano-haskell-packages
-- update either of these.
index-state:
-- Bump this if you need newer packages from Hackage
, hackage.haskell.org 2025-10-23T13:39:53Z
, hackage.haskell.org 2025-12-01T13:39:53Z
-- Bump this if you need newer packages from CHaP
, cardano-haskell-packages 2025-10-01T14:54:25Z
, cardano-haskell-packages 2025-12-01T07:41:27Z

packages:
ouroboros-consensus
Expand Down Expand Up @@ -53,8 +53,8 @@ if impl (ghc >= 9.10)
source-repository-package
type: git
location: https://github.com/IntersectMBO/cardano-ledger
tag: fb09078fa55015c881303a2ddb609c024cec258f
--sha256: sha256-9Y9CRiyMn0AWD+C4aNVMaJgrj3FDAYfCX4VrLvtoMaI=
tag: f4dec1cb721e23f02aefbd74674c9f343bca61db
--sha256: sha256-yrdAtIzTQCgMuTpMEA5ch8op5MdSp47cXI90Nbp4KLU=
subdir:
eras/allegra/impl
eras/alonzo/impl
Expand All @@ -73,7 +73,6 @@ source-repository-package
libs/non-integral
libs/small-steps
libs/cardano-data
libs/set-algebra
libs/vector-map
eras/byron/chain/executable-spec
eras/byron/ledger/executable-spec
Expand Down
12 changes: 6 additions & 6 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

17 changes: 8 additions & 9 deletions ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -142,16 +142,16 @@ library
cardano-ledger-allegra ^>=1.9,
cardano-ledger-alonzo ^>=1.15,
cardano-ledger-api ^>=1.13,
cardano-ledger-babbage ^>=1.12,
cardano-ledger-binary ^>=1.7,
cardano-ledger-byron ^>=1.2,
cardano-ledger-babbage ^>=1.13,
cardano-ledger-binary ^>=1.8,
cardano-ledger-byron ^>=1.3,
cardano-ledger-conway ^>=1.21,
cardano-ledger-core ^>=1.19,
cardano-ledger-dijkstra ^>=0.2,
cardano-ledger-mary ^>=1.9,
cardano-ledger-shelley ^>=1.17,
cardano-ledger-mary ^>=1.10,
cardano-ledger-shelley ^>=1.18,
cardano-prelude,
cardano-protocol-tpraos ^>=1.4.1,
cardano-protocol-tpraos ^>=1.5,
cardano-slotting,
cardano-strict-containers,
cborg ^>=0.2.2,
Expand Down Expand Up @@ -238,8 +238,7 @@ library unstable-byron-testlib
cardano-binary,
cardano-crypto,
cardano-crypto-class,
cardano-crypto-test,
cardano-crypto-wrapper,
cardano-crypto-wrapper:{cardano-crypto-wrapper, testlib},
cardano-ledger-binary:{cardano-ledger-binary, testlib},
cardano-ledger-byron:{cardano-ledger-byron, testlib},
cardano-ledger-core,
Expand Down Expand Up @@ -570,7 +569,7 @@ library unstable-cardano-tools
cardano-ledger-mary,
cardano-ledger-shelley,
cardano-prelude,
cardano-protocol-tpraos ^>=1.4.1,
cardano-protocol-tpraos ^>=1.5,
cardano-slotting,
cardano-strict-containers,
cborg ^>=0.2.2,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,10 @@ import qualified Cardano.Ledger.Conway.Rules as SL
)
import qualified Cardano.Ledger.Conway.State as CG
import Cardano.Ledger.Dijkstra (DijkstraEra)
import qualified Cardano.Ledger.Dijkstra.Rules as Dijkstra
import qualified Cardano.Ledger.Dijkstra.Rules as SL
(DijkstraLedgerPredFailure (..)
)
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Shelley (ShelleyEra)
import qualified Cardano.Ledger.Shelley.API as SL
Expand Down Expand Up @@ -123,11 +127,11 @@ class
SL.LedgerEnv era ->
SL.LedgerState era ->
WhetherToIntervene ->
Core.Tx era ->
Core.Tx TopTx era ->
Except
(SL.ApplyTxError era)
( SL.LedgerState era
, SL.Validated (Core.Tx era)
, SL.Validated (Core.Tx TopTx era)
)

-- | Whether the era has an instance of 'CG.ConwayEraGov'
Expand All @@ -148,11 +152,11 @@ defaultApplyShelleyBasedTx ::
SL.LedgerEnv era ->
SL.LedgerState era ->
WhetherToIntervene ->
Core.Tx era ->
Core.Tx TopTx era ->
Except
(SL.ApplyTxError era)
( SL.LedgerState era
, SL.Validated (Core.Tx era)
, SL.Validated (Core.Tx TopTx era)
)
defaultApplyShelleyBasedTx globals ledgerEnv mempoolState _wti tx =
liftEither $
Expand Down Expand Up @@ -210,11 +214,11 @@ applyAlonzoBasedTx ::
SL.LedgerEnv era ->
SL.LedgerState era ->
WhetherToIntervene ->
Core.Tx era ->
Core.Tx TopTx era ->
Except
(SL.ApplyTxError era)
( SL.LedgerState era
, SL.Validated (Core.Tx era)
, SL.Validated (Core.Tx TopTx era)
)
applyAlonzoBasedTx globals ledgerEnv mempoolState wti tx = do
(mempoolState', vtx) <-
Expand Down Expand Up @@ -318,9 +322,9 @@ instance SupportsTwoPhaseValidation ConwayEra where

instance SupportsTwoPhaseValidation DijkstraEra where
isIncorrectClaimedFlag _ = \case
SL.ConwayUtxowFailure
( Conway.UtxoFailure
( Conway.UtxosFailure
SL.DijkstraUtxowFailure
( Dijkstra.UtxoFailure
( Dijkstra.UtxosFailure
( Conway.ValidationTagMismatch
(Alonzo.IsValid _claimedFlag)
_validationErrs
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ import Cardano.Protocol.Crypto (Crypto)
import qualified Cardano.Protocol.TPraos.BHeader as SL
import qualified Data.ByteString.Lazy as Lazy
import Data.Coerce (coerce)
import Data.Either (fromRight)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
Expand Down Expand Up @@ -311,7 +312,9 @@ decodeShelleyBlock ::
ShelleyCompatible proto era =>
forall s.
Plain.Decoder s (Lazy.ByteString -> ShelleyBlock proto era)
decodeShelleyBlock = eraDecoder @era $ (. Full) . runAnnotator <$> decCBOR
decodeShelleyBlock =
eraDecoder @era $
(. Full) . (fromRight (error "TODO(geo2a): remove fromRight") .) . runAnnotator <$> decCBOR

shelleyBinaryBlockInfo ::
forall proto era. ShelleyCompatible proto era => ShelleyBlock proto era -> BinaryBlockInfo
Expand All @@ -335,7 +338,9 @@ decodeShelleyHeader ::
ShelleyCompatible proto era =>
forall s.
Plain.Decoder s (Lazy.ByteString -> Header (ShelleyBlock proto era))
decodeShelleyHeader = eraDecoder @era $ (. Full) . runAnnotator <$> decCBOR
decodeShelleyHeader =
eraDecoder @era $
(. Full) . (fromRight (error "TODO(geo2a): remove fromRight") .) . runAnnotator <$> decCBOR

{-------------------------------------------------------------------------------
Condense
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,8 @@ data instance BlockConfig (ShelleyBlock proto era) = ShelleyConfig
, shelleyNetworkMagic :: !NetworkMagic
, shelleyBlockIssuerVKeys ::
!( Map
(SL.KeyHash 'SL.BlockIssuer)
(SL.VKey 'SL.BlockIssuer)
(SL.KeyHash SL.BlockIssuer)
(SL.VKey SL.BlockIssuer)
)
-- ^ For nodes that can produce blocks, this should be set to the
-- verification key(s) corresponding to the node's signing key(s). For non
Expand All @@ -70,7 +70,7 @@ mkShelleyBlockConfig ::
ShelleyBasedEra era =>
SL.ProtVer ->
SL.ShelleyGenesis ->
[SL.VKey 'SL.BlockIssuer] ->
[SL.VKey SL.BlockIssuer] ->
BlockConfig (ShelleyBlock proto era)
mkShelleyBlockConfig protVer genesis blockIssuerVKeys =
ShelleyConfig
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@

module Ouroboros.Consensus.Shelley.Ledger.Forge (forgeShelleyBlock) where

import qualified Cardano.Ledger.Core as Core (Tx)
import qualified Cardano.Ledger.Core as Core (TopTx, Tx)
import qualified Cardano.Ledger.Core as SL (hashBlockBody, mkBasicBlockBody, txSeqBlockBodyL)
import qualified Cardano.Ledger.Shelley.API as SL (Block (..), extractTx)
import qualified Cardano.Ledger.Shelley.BlockBody as SL (bBodySize)
Expand Down Expand Up @@ -85,7 +85,7 @@ forgeShelleyBlock

actualBodySize = SL.bBodySize protocolVersion body

extractTx :: Validated (GenTx (ShelleyBlock proto era)) -> Core.Tx era
extractTx :: Validated (GenTx (ShelleyBlock proto era)) -> Core.Tx Core.TopTx era
extractTx (ShelleyValidatedTx _txid vtx) = SL.extractTx vtx

prevHash :: SL.PrevHash
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ import qualified Cardano.Crypto.Hash as Hash
import qualified Cardano.Ledger.Allegra.Rules as AllegraEra
import Cardano.Ledger.Alonzo.Core
( BlockBody
, TopTx
, Tx
, allInputsTxBodyF
, bodyTxL
Expand Down Expand Up @@ -77,6 +78,7 @@ import Cardano.Ledger.Binary
import qualified Cardano.Ledger.Conway.PParams as SL
import qualified Cardano.Ledger.Conway.Rules as ConwayEra
import qualified Cardano.Ledger.Conway.UTxO as SL
import qualified Cardano.Ledger.Dijkstra.Rules as DijkstraEra
import qualified Cardano.Ledger.Hashes as SL
import qualified Cardano.Ledger.Shelley.API as SL
import qualified Cardano.Ledger.Shelley.Rules as ShelleyEra
Expand All @@ -86,6 +88,7 @@ import Control.Monad (guard)
import Control.Monad.Except (Except, liftEither)
import Control.Monad.Identity (Identity (..))
import Data.DerivingVia (InstantiatedAt (..))
import Data.Either (fromRight)
import Data.Foldable (toList)
import Data.Measure (Measure)
import Data.Typeable (Typeable)
Expand All @@ -112,7 +115,7 @@ import Ouroboros.Consensus.Util (ShowProxy (..), coerceSet)
import Ouroboros.Consensus.Util.Condense
import Ouroboros.Network.Block (unwrapCBORinCBOR, wrapCBORinCBOR)

data instance GenTx (ShelleyBlock proto era) = ShelleyTx !SL.TxId !(Tx era)
data instance GenTx (ShelleyBlock proto era) = ShelleyTx !SL.TxId !(Tx TopTx era)
deriving stock Generic

deriving instance ShelleyBasedEra era => NoThunks (GenTx (ShelleyBlock proto era))
Expand All @@ -126,7 +129,7 @@ instance
data instance Validated (GenTx (ShelleyBlock proto era))
= ShelleyValidatedTx
!SL.TxId
!(SL.Validated (Tx era))
!(SL.Validated (Tx TopTx era))
deriving stock Generic

deriving instance ShelleyBasedEra era => NoThunks (Validated (GenTx (ShelleyBlock proto era)))
Expand Down Expand Up @@ -186,13 +189,14 @@ instance
coerceSet
(tx ^. bodyTxL . allInputsTxBodyF)

mkShelleyTx :: forall era proto. ShelleyBasedEra era => Tx era -> GenTx (ShelleyBlock proto era)
mkShelleyTx ::
forall era proto. ShelleyBasedEra era => Tx TopTx era -> GenTx (ShelleyBlock proto era)
mkShelleyTx tx = ShelleyTx (txIdTx tx) tx

mkShelleyValidatedTx ::
forall era proto.
ShelleyBasedEra era =>
SL.Validated (Tx era) ->
SL.Validated (Tx TopTx era) ->
Validated (GenTx (ShelleyBlock proto era))
mkShelleyValidatedTx vtx = ShelleyValidatedTx txid vtx
where
Expand All @@ -202,7 +206,7 @@ newtype instance TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId SL.TxId
deriving newtype (Eq, Ord, NoThunks)

deriving newtype instance
(Typeable era, Typeable proto, Crypto (ProtoCrypto proto)) =>
Crypto (ProtoCrypto proto) =>
EncCBOR (TxId (GenTx (ShelleyBlock proto era)))
deriving newtype instance
(Typeable era, Typeable proto, Crypto (ProtoCrypto proto)) =>
Expand All @@ -226,7 +230,7 @@ instance ShelleyBasedEra era => HasTxs (ShelleyBlock proto era) where
. SL.blockBody
. shelleyBlockRaw
where
blockBodyToTxList :: BlockBody era -> [Tx era]
blockBodyToTxList :: BlockBody era -> [Tx TopTx era]
blockBodyToTxList blockBody = toList $ blockBody ^. txSeqBlockBodyL

{-------------------------------------------------------------------------------
Expand All @@ -243,7 +247,7 @@ instance ShelleyCompatible proto era => FromCBOR (GenTx (ShelleyBlock proto era)
fmap mkShelleyTx $
unwrapCBORinCBOR $
eraDecoder @era $
(. Full) . runAnnotator <$> decCBOR
(. Full) . (fromRight (error "TODO(geo2a): remove fromRight") .) . runAnnotator <$> decCBOR

{-------------------------------------------------------------------------------
Pretty-printing
Expand Down Expand Up @@ -480,9 +484,9 @@ instance MaxTxSizeUTxO ConwayEra where
instance MaxTxSizeUTxO DijkstraEra where
maxTxSizeUTxO txSize txSizeLimit =
SL.ApplyTxError . pure $
ConwayEra.ConwayUtxowFailure $
ConwayEra.UtxoFailure $
ConwayEra.MaxTxSizeUTxO $
DijkstraEra.DijkstraUtxowFailure $
DijkstraEra.UtxoFailure $
DijkstraEra.MaxTxSizeUTxO $
L.Mismatch
{ mismatchSupplied = txSize
, mismatchExpected = txSizeLimit
Expand Down Expand Up @@ -617,9 +621,9 @@ instance ExUnitsTooBigUTxO ConwayEra where
instance ExUnitsTooBigUTxO DijkstraEra where
exUnitsTooBigUTxO txsz limit =
SL.ApplyTxError . pure $
ConwayEra.ConwayUtxowFailure $
ConwayEra.UtxoFailure $
ConwayEra.ExUnitsTooBigUTxO $
DijkstraEra.DijkstraUtxowFailure $
DijkstraEra.UtxoFailure $
DijkstraEra.ExUnitsTooBigUTxO $
L.Mismatch
{ mismatchSupplied = txsz
, mismatchExpected = limit
Expand Down Expand Up @@ -761,7 +765,7 @@ instance TxRefScriptsSizeTooBig ConwayEra where
instance TxRefScriptsSizeTooBig DijkstraEra where
txRefScriptsSizeTooBig txsz limit =
SL.ApplyTxError . pure $
ConwayEra.ConwayTxRefScriptsSizeTooBig $
DijkstraEra.DijkstraTxRefScriptsSizeTooBig $
L.Mismatch
{ mismatchSupplied = txsz
, mismatchExpected = limit
Expand Down
Loading
Loading