Skip to content

Commit a7085d8

Browse files
lehinsSoupstraw
andcommitted
Introduce transaction level concept for Nested Transactions:
* Add `Cardano.Ledger.Core.TxLevel` module with level definitions * Apply transaction level throught the ledegr codebase * Add DijkstraSubTx * Added DijkstraSubTxBody Co-authored-by: Joosep Jääger <joosep.jaager@iohk.io>
1 parent 237fed8 commit a7085d8

File tree

233 files changed

+3630
-2352
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

233 files changed

+3630
-2352
lines changed

eras/allegra/impl/CHANGELOG.md

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,11 @@
22

33
## 1.9.0.0
44

5+
* Add `invalidBeforeL`, `invalidHereAfterL`
6+
* Add `basicAllegraTxBody`
7+
* Add `TxLevel` argument to `Tx` and `TxBody`
8+
* Add `HasEraTxLevel` instances for `Tx` and `TxBody`
9+
* Add `EraTxLevel` instance
510
* Remove deprecated `timelockScriptsTxAuxDataL`
611

712
### `testlib`

eras/allegra/impl/cardano-ledger-allegra.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -127,6 +127,7 @@ library testlib
127127
microlens,
128128
small-steps,
129129
text,
130+
tree-diff,
130131

131132
executable huddle-cddl
132133
main-is: Main.hs

eras/allegra/impl/src/Cardano/Ledger/Allegra/Era.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,9 @@ import Cardano.Ledger.Shelley.Rules
2424

2525
instance EraGenesis AllegraEra
2626

27+
instance EraTxLevel AllegraEra where
28+
type STxLevel l AllegraEra = STxTopLevel l AllegraEra
29+
2730
--------------------------------------------------------------------------------
2831
-- Core instances
2932
--------------------------------------------------------------------------------

eras/allegra/impl/src/Cardano/Ledger/Allegra/Rules/Utxo.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -242,7 +242,7 @@ utxoTransition = do
242242
validateOutsideValidityIntervalUTxO ::
243243
AllegraEraTxBody era =>
244244
SlotNo ->
245-
TxBody era ->
245+
TxBody l era ->
246246
Test (AllegraUtxoPredFailure era)
247247
validateOutsideValidityIntervalUTxO slot txb =
248248
failureUnless (inInterval slot (txb ^. vldtTxBodyL)) $
@@ -314,7 +314,7 @@ instance
314314
STS (AllegraUTXO era)
315315
where
316316
type State (AllegraUTXO era) = Shelley.UTxOState era
317-
type Signal (AllegraUTXO era) = Tx era
317+
type Signal (AllegraUTXO era) = Tx TopTx era
318318
type Environment (AllegraUTXO era) = Shelley.UtxoEnv era
319319
type BaseM (AllegraUTXO era) = ShelleyBase
320320
type PredicateFailure (AllegraUTXO era) = AllegraUtxoPredFailure era

eras/allegra/impl/src/Cardano/Ledger/Allegra/Rules/Utxow.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,15 +58,15 @@ instance
5858
Embed (EraRule "UTXO" era) (AllegraUTXOW era)
5959
, Environment (EraRule "UTXO" era) ~ UtxoEnv era
6060
, State (EraRule "UTXO" era) ~ UTxOState era
61-
, Signal (EraRule "UTXO" era) ~ Tx era
61+
, Signal (EraRule "UTXO" era) ~ Tx TopTx era
6262
, EraRule "UTXOW" era ~ AllegraUTXOW era
6363
, InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure era
6464
, EraCertState era
6565
) =>
6666
STS (AllegraUTXOW era)
6767
where
6868
type State (AllegraUTXOW era) = UTxOState era
69-
type Signal (AllegraUTXOW era) = Tx era
69+
type Signal (AllegraUTXOW era) = Tx TopTx era
7070
type Environment (AllegraUTXOW era) = UtxoEnv era
7171
type BaseM (AllegraUTXOW era) = ShelleyBase
7272
type PredicateFailure (AllegraUTXOW era) = ShelleyUtxowPredFailure era

eras/allegra/impl/src/Cardano/Ledger/Allegra/Scripts.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,8 @@ module Cardano.Ledger.Allegra.Scripts (
5555
upgradeMultiSig,
5656
lteNegInfty,
5757
ltePosInfty,
58+
invalidBeforeL,
59+
invalidHereAfterL,
5860
) where
5961

6062
import Cardano.Ledger.Allegra.Era (AllegraEra)
@@ -109,6 +111,7 @@ import Data.Sequence.Strict as Seq (StrictSeq (Empty, (:<|)))
109111
import qualified Data.Sequence.Strict as SSeq
110112
import qualified Data.Set as Set (Set, member)
111113
import GHC.Generics (Generic)
114+
import Lens.Micro (Lens', lens)
112115
import NoThunks.Class (NoThunks (..))
113116

114117
-- | ValidityInterval is a half open interval. Closed on the bottom, open on the top.
@@ -119,6 +122,14 @@ data ValidityInterval = ValidityInterval
119122
}
120123
deriving (Ord, Eq, Generic, Show, NoThunks, NFData)
121124

125+
-- | Lens to access the 'invalidBefore' field of a 'ValidityInterval' as a 'StrictMaybe SlotNo'.
126+
invalidBeforeL :: Lens' ValidityInterval (StrictMaybe SlotNo)
127+
invalidBeforeL = lens invalidBefore (\vi before -> vi {invalidBefore = before})
128+
129+
-- | Lens to access the 'invalidHereAfter' field of a 'ValidityInterval' as a 'StrictMaybe SlotNo'.
130+
invalidHereAfterL :: Lens' ValidityInterval (StrictMaybe SlotNo)
131+
invalidHereAfterL = lens invalidHereafter (\vi hereAfter -> vi {invalidHereafter = hereAfter})
132+
122133
encodeVI :: ValidityInterval -> Encode ('Closed 'Dense) ValidityInterval
123134
encodeVI (ValidityInterval f t) = Rec ValidityInterval !> To f !> To t
124135

eras/allegra/impl/src/Cardano/Ledger/Allegra/Translation.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -71,8 +71,8 @@ instance TranslateEra AllegraEra NewEpochState where
7171
stashedAVVMAddresses = ()
7272
}
7373

74-
instance TranslateEra AllegraEra Tx where
75-
type TranslationError AllegraEra Tx = DecoderError
74+
instance TranslateEra AllegraEra (Tx TopTx) where
75+
type TranslationError AllegraEra (Tx TopTx) = DecoderError
7676
translateEra _ctx = translateEraThroughCBOR "ShelleyTx"
7777

7878
--------------------------------------------------------------------------------

eras/allegra/impl/src/Cardano/Ledger/Allegra/Tx.hs

Lines changed: 13 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,9 @@
33
{-# LANGUAGE FlexibleContexts #-}
44
{-# LANGUAGE FlexibleInstances #-}
55
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
6+
{-# LANGUAGE MultiParamTypeClasses #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
8+
{-# LANGUAGE TypeApplications #-}
79
{-# LANGUAGE TypeFamilies #-}
810
{-# LANGUAGE TypeOperators #-}
911
{-# LANGUAGE UndecidableInstances #-}
@@ -24,7 +26,9 @@ import Cardano.Ledger.Binary (Annotator, DecCBOR (..), EncCBOR, ToCBOR)
2426
import Cardano.Ledger.Core (
2527
EraTx (..),
2628
EraTxWits (..),
29+
HasEraTxLevel (..),
2730
NativeScript,
31+
STxTopLevel (..),
2832
)
2933
import Cardano.Ledger.Keys.WitVKey (witVKeyHash)
3034
import Cardano.Ledger.MemoBytes (EqRaw (..))
@@ -41,14 +45,15 @@ import Cardano.Ledger.Shelley.Tx (
4145
)
4246
import Control.DeepSeq (NFData)
4347
import qualified Data.Set as Set (map)
48+
import Data.Typeable (Typeable)
4449
import GHC.Generics (Generic)
4550
import Lens.Micro (Lens', lens, (^.))
4651
import NoThunks.Class (NoThunks)
4752

4853
-- ========================================
4954

5055
instance EraTx AllegraEra where
51-
newtype Tx AllegraEra = MkAllegraTx {unAllegraTx :: ShelleyTx AllegraEra}
56+
newtype Tx t AllegraEra = MkAllegraTx {unAllegraTx :: ShelleyTx t AllegraEra}
5257
deriving newtype (Eq, NFData, NoThunks, Show, ToCBOR, EncCBOR)
5358
deriving (Generic)
5459

@@ -71,13 +76,16 @@ instance EraTx AllegraEra where
7176

7277
getMinFeeTx pp tx _ = shelleyMinFeeTx pp tx
7378

74-
instance EqRaw (Tx AllegraEra) where
79+
instance HasEraTxLevel Tx AllegraEra where
80+
toSTxLevel (MkAllegraTx ShelleyTx {}) = STopTxOnly @AllegraEra
81+
82+
instance EqRaw (Tx t AllegraEra) where
7583
eqRaw = shelleyTxEqRaw
7684

77-
instance DecCBOR (Annotator (Tx AllegraEra)) where
85+
instance Typeable t => DecCBOR (Annotator (Tx t AllegraEra)) where
7886
decCBOR = fmap MkAllegraTx <$> decCBOR
7987

80-
allegraTxL :: Lens' (Tx AllegraEra) (ShelleyTx AllegraEra)
88+
allegraTxL :: Lens' (Tx t AllegraEra) (ShelleyTx t AllegraEra)
8189
allegraTxL = lens unAllegraTx (\x y -> x {unAllegraTx = y})
8290

8391
-- =======================================================
@@ -87,7 +95,7 @@ allegraTxL = lens unAllegraTx (\x y -> x {unAllegraTx = y})
8795

8896
validateTimelock ::
8997
(EraTx era, AllegraEraTxBody era, AllegraEraScript era, NativeScript era ~ Timelock era) =>
90-
Tx era -> NativeScript era -> Bool
98+
Tx t era -> NativeScript era -> Bool
9199
validateTimelock tx timelock = evalTimelock vhks (tx ^. bodyTxL . vldtTxBodyL) timelock
92100
where
93101
vhks = Set.map witVKeyHash (tx ^. witsTxL . addrTxWitsL)

0 commit comments

Comments
 (0)