Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Run conformance on passTick #4762

Closed
wants to merge 2 commits into from
Closed
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
87 changes: 64 additions & 23 deletions eras/conway/impl/testlib/Test/Cardano/Ledger/Conway/Imp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

module Test.Cardano.Ledger.Conway.Imp (spec) where
module Test.Cardano.Ledger.Conway.Imp (spec, conwaySpec) where

import Cardano.Ledger.Alonzo.Plutus.Context (EraPlutusContext (..))
import Cardano.Ledger.Alonzo.Rules (
Expand Down Expand Up @@ -54,18 +54,23 @@ import qualified Test.Cardano.Ledger.Conway.Imp.LedgerSpec as Ledger
import qualified Test.Cardano.Ledger.Conway.Imp.RatifySpec as Ratify
import qualified Test.Cardano.Ledger.Conway.Imp.UtxoSpec as Utxo
import qualified Test.Cardano.Ledger.Conway.Imp.UtxosSpec as Utxos
import Test.Cardano.Ledger.Conway.ImpTest (ConwayEraImp, LedgerSpec, modifyImpInitProtVer)
import Test.Cardano.Ledger.Conway.ImpTest (
ConwayEraImp,
LedgerSpec,
modifyImpInitProtVer,
)
import Test.Cardano.Ledger.Imp.Common
import Test.Cardano.Ledger.Shelley.ImpTest (ImpInit)

spec ::
forall era.
( Arbitrary (TxAuxData era)
, ConwayEraImp era
, EraSegWits era
, InjectRuleFailure "LEDGER" ConwayGovPredFailure era
, InjectRuleFailure "LEDGER" ConwayCertsPredFailure era
, Inject (BabbageContextError era) (ContextError era)
, Inject (ConwayContextError era) (ContextError era)
, InjectRuleFailure "LEDGER" ConwayGovPredFailure era
, InjectRuleFailure "LEDGER" ConwayCertsPredFailure era
, InjectRuleFailure "LEDGER" BabbageUtxoPredFailure era
, InjectRuleFailure "LEDGER" BabbageUtxowPredFailure era
, InjectRuleFailure "LEDGER" AlonzoUtxoPredFailure era
Expand All @@ -77,38 +82,74 @@ spec ::
, InjectRuleFailure "LEDGER" ConwayGovCertPredFailure era
, InjectRuleFailure "LEDGER" ConwayLedgerPredFailure era
, InjectRuleFailure "BBODY" ConwayBbodyPredFailure era
, InjectRuleEvent "TICK" ConwayEpochEvent era
, Event (EraRule "EPOCH" era) ~ ConwayEpochEvent era
, Event (EraRule "NEWEPOCH" era) ~ ConwayNewEpochEvent era
, Event (EraRule "MEMPOOL" era) ~ ConwayMempoolEvent era
, Event (EraRule "LEDGERS" era) ~ ShelleyLedgersEvent era
, Event (EraRule "LEDGER" era) ~ ConwayLedgerEvent era
, Event (EraRule "HARDFORK" era) ~ ConwayHardForkEvent era
, BaseM (EraRule "LEDGERS" era) ~ ShelleyBase
, Environment (EraRule "LEDGERS" era) ~ ShelleyLedgersEnv era
, Signal (EraRule "LEDGERS" era) ~ Seq (Tx era)
, STS (EraRule "LEDGERS" era)
, ApplyTx era
, NFData (Event (EraRule "ENACT" era))
, ToExpr (Event (EraRule "ENACT" era))
, Eq (Event (EraRule "ENACT" era))
, Typeable (Event (EraRule "ENACT" era))
) =>
Spec
spec = do
BabbageImp.spec @era
withImpInit @(LedgerSpec era) $ conwaySpec @era

conwaySpec ::
forall era.
( ConwayEraImp era
, EraSegWits era
, Inject (BabbageContextError era) (ContextError era)
, Inject (ConwayContextError era) (ContextError era)
, InjectRuleFailure "LEDGER" ConwayGovPredFailure era
, InjectRuleFailure "LEDGER" ConwayCertsPredFailure era
, InjectRuleFailure "LEDGER" BabbageUtxoPredFailure era
, InjectRuleFailure "LEDGER" AlonzoUtxosPredFailure era
, InjectRuleFailure "LEDGER" AlonzoUtxowPredFailure era
, InjectRuleFailure "LEDGER" ShelleyUtxowPredFailure era
, InjectRuleFailure "LEDGER" ConwayDelegPredFailure era
, InjectRuleFailure "LEDGER" ConwayGovCertPredFailure era
, InjectRuleFailure "LEDGER" ConwayLedgerPredFailure era
, InjectRuleFailure "BBODY" ConwayBbodyPredFailure era
, InjectRuleEvent "TICK" ConwayEpochEvent era
, Event (EraRule "EPOCH" era) ~ ConwayEpochEvent era
, Event (EraRule "NEWEPOCH" era) ~ ConwayNewEpochEvent era
, Event (EraRule "MEMPOOL" era) ~ ConwayMempoolEvent era
, Event (EraRule "LEDGERS" era) ~ ShelleyLedgersEvent era
, Event (EraRule "LEDGER" era) ~ ConwayLedgerEvent era
, Event (EraRule "HARDFORK" era) ~ ConwayHardForkEvent era
, BaseM (EraRule "LEDGERS" era) ~ ShelleyBase
, Environment (EraRule "LEDGERS" era) ~ ShelleyLedgersEnv era
, Signal (EraRule "LEDGERS" era) ~ Seq (Tx era)
, STS (EraRule "LEDGERS" era)
, ApplyTx era
, Event (EraRule "HARDFORK" era) ~ ConwayHardForkEvent era
, NFData (Event (EraRule "ENACT" era))
, ToExpr (Event (EraRule "ENACT" era))
, Eq (Event (EraRule "ENACT" era))
, Typeable (Event (EraRule "ENACT" era))
) =>
Spec
spec = do
BabbageImp.spec @era
withImpInit @(LedgerSpec era) $
forM_ (eraProtVersions @era) $ \protVer ->
describe ("ConwayImpSpec - " <> show protVer) $
modifyImpInitProtVer protVer $ do
describe "BBODY" Bbody.spec
describe "CERTS" Certs.spec
describe "DELEG" Deleg.spec
describe "ENACT" Enact.spec
describe "EPOCH" Epoch.spec
describe "GOV" Gov.spec
describe "GOVCERT" GovCert.spec
describe "LEDGER" Ledger.spec
describe "RATIFY" Ratify.spec
describe "UTXO" Utxo.spec
describe "UTXOS" Utxos.spec
SpecWith (ImpInit (LedgerSpec era))
conwaySpec = do
forM_ (eraProtVersions @era) $ \protVer ->
describe ("ConwayImpSpec - " <> show protVer) $
modifyImpInitProtVer protVer $ do
describe "BBODY" Bbody.spec
describe "CERTS" Certs.spec
describe "DELEG" Deleg.spec
describe "ENACT" Enact.spec
describe "EPOCH" Epoch.spec
describe "GOV" Gov.spec
describe "GOVCERT" GovCert.spec
describe "LEDGER" Ledger.spec
describe "RATIFY" Ratify.spec
describe "UTXO" Utxo.spec
describe "UTXOS" Utxos.spec
4 changes: 4 additions & 0 deletions eras/shelley/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,10 @@

### `testlib`

* Add `iteHook` to `ImpTesEnv` for additionally checking conformance with ImpTests. #4748
* Add lens `iteHookL`.
* Add `withHook` modifier for `ImpTestM era a`
* Add `modifyImpInitHook`.
* Switch to using `ImpSpec` package
* Remove: `runImpTestM`, `runImpTestM_`, `evalImpTestM`, `execImpTestM`, `runImpTestGenM`, `runImpTestGenM_`, `evalImpTestGenM`, `execImpTestGenM`, `withImpState` and `withImpStateModified`.
* Add `LedgerSpec`, `modifyImpInitProtVer`.
Expand Down
95 changes: 85 additions & 10 deletions eras/shelley/impl/testlib/Test/Cardano/Ledger/Shelley/ImpTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,6 +99,8 @@ module Test.Cardano.Ledger.Shelley.ImpTest (
impEraStartEpochNo,
impSetSeed,
modifyImpInitProtVer,
modifyImpInitHook,
modifyImpInitPassTickHook,

-- * Logging
Doc,
Expand All @@ -117,6 +119,8 @@ module Test.Cardano.Ledger.Shelley.ImpTest (
withPostFixup,
withPreFixup,
withCborRoundTripFailures,
withHook,
withPassTickHook,
impNESL,
impGlobalsL,
impLastTickG,
Expand Down Expand Up @@ -302,6 +306,8 @@ instance ShelleyEraImp era => ImpSpec (LedgerSpec era) where
ImpTestEnv
{ iteFixup = fixupTx
, iteCborRoundTripFailures = True
, iteHook = \_ _ _ _ -> pure ()
, itePassTickHook = pure ()
}
, impInitState = initState
}
Expand Down Expand Up @@ -618,16 +624,38 @@ modifyImpInitProtVer ::
SpecWith (ImpInit (LedgerSpec era)) ->
SpecWith (ImpInit (LedgerSpec era))
modifyImpInitProtVer ver =
modifyImpInit $ \impInit ->
impInit
{ impInitState =
impInitState impInit
& impNESL
. nesEsL
. curPParamsEpochStateL
. ppProtocolVersionL
.~ ProtVer ver 0
}
modifyImpInit
( impInitStateL
. impNESL
. nesEsL
. curPParamsEpochStateL @era
. ppProtocolVersionL
.~ ProtVer ver 0
)

modifyImpInitHook ::
forall era.
ShelleyEraImp era =>
( Either
(NonEmpty (PredicateFailure (EraRule "LEDGER" era)))
(State (EraRule "LEDGER" era), [Event (EraRule "LEDGER" era)]) ->
LedgerEnv era ->
LedgerState era ->
Tx era ->
ImpTestM era ()
) ->
SpecWith (ImpInit (LedgerSpec era)) ->
SpecWith (ImpInit (LedgerSpec era))
modifyImpInitHook f =
modifyImpInit (impInitEnvL . iteHookL .~ f)

modifyImpInitPassTickHook ::
forall era.
ImpTestM era () ->
SpecWith (ImpInit (LedgerSpec era)) ->
SpecWith (ImpInit (LedgerSpec era))
modifyImpInitPassTickHook f =
modifyImpInit (impInitEnvL . itePassTickHookL .~ f)

impLedgerEnv :: EraGov era => NewEpochState era -> ImpTestM era (LedgerEnv era)
impLedgerEnv nes = do
Expand Down Expand Up @@ -767,13 +795,38 @@ impWitsVKeyNeeded txBody = do

data ImpTestEnv era = ImpTestEnv
{ iteFixup :: Tx era -> ImpTestM era (Tx era)
, iteHook ::
Either
(NonEmpty (PredicateFailure (EraRule "LEDGER" era)))
(State (EraRule "LEDGER" era), [Event (EraRule "LEDGER" era)]) ->
LedgerEnv era ->
LedgerState era ->
Tx era ->
ImpTestM era ()
, itePassTickHook :: ImpTestM era ()
, iteCborRoundTripFailures :: !Bool
-- ^ Expect failures in CBOR round trip serialization tests for predicate failures
}

iteFixupL :: Lens' (ImpTestEnv era) (Tx era -> ImpTestM era (Tx era))
iteFixupL = lens iteFixup (\x y -> x {iteFixup = y})

iteHookL ::
Lens'
(ImpTestEnv era)
( Either
(NonEmpty (PredicateFailure (EraRule "LEDGER" era)))
(State (EraRule "LEDGER" era), [Event (EraRule "LEDGER" era)]) ->
LedgerEnv era ->
LedgerState era ->
Tx era ->
ImpTestM era ()
)
iteHookL = lens iteHook (\x y -> x {iteHook = y})

itePassTickHookL :: Lens' (ImpTestEnv era) (ImpTestM era ())
itePassTickHookL = lens itePassTickHook (\x y -> x {itePassTickHook = y})

iteCborRoundTripFailuresL :: Lens' (ImpTestEnv era) Bool
iteCborRoundTripFailuresL = lens iteCborRoundTripFailures (\x y -> x {iteCborRoundTripFailures = y})

Expand Down Expand Up @@ -1032,6 +1085,10 @@ trySubmitTx tx = do
ImpTestState {impRootTxIn} <- get
res <- tryRunImpRule @"LEDGER" lEnv (st ^. nesEsL . esLStateL) txFixed
roundTripCheck <- asks iteCborRoundTripFailures

-- Check for conformance
asks iteHook >>= (\f -> f res lEnv (st ^. nesEsL . esLStateL) txFixed)

case res of
Left predFailures -> do
-- Verify that produced predicate failures are ready for the node-to-client protocol
Expand Down Expand Up @@ -1178,6 +1235,7 @@ passTick ::
) =>
ImpTestM era ()
passTick = do
impAnn "Running passTickHook" =<< asks itePassTickHook
impLastTick <- gets impLastTick
curNES <- getsNES id
nes <- runImpRule @"TICK" () curNES impLastTick
Expand Down Expand Up @@ -1551,6 +1609,23 @@ withPostFixup ::
ImpTestM era a
withPostFixup f = withCustomFixup (>=> f)

-- | Replace the hook with the given hook
withHook ::
( Either
(NonEmpty (PredicateFailure (EraRule "LEDGER" era)))
(State (EraRule "LEDGER" era), [Event (EraRule "LEDGER" era)]) ->
LedgerEnv era ->
LedgerState era ->
Tx era ->
ImpTestM era ()
) ->
ImpTestM era a ->
ImpTestM era a
withHook f = local $ iteHookL .~ f

withPassTickHook :: ImpTestM era () -> ImpTestM era a -> ImpTestM era a
withPassTickHook f = local $ itePassTickHookL .~ f

expectUTxOContent ::
(HasCallStack, ToExpr (TxOut era)) =>
UTxO era -> [(TxIn (EraCrypto era), Maybe (TxOut era) -> Bool)] -> ImpTestM era ()
Expand Down
3 changes: 2 additions & 1 deletion libs/ImpSpec/ImpSpec.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,8 @@ library
prettyprinter-ansi-terminal,
random,
text,
unliftio
unliftio,
microlens

test-suite tests
type: exitcode-stdio-1.0
Expand Down
7 changes: 7 additions & 0 deletions libs/ImpSpec/src/Test/ImpSpec/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Data.Proxy (Proxy (..))
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import GHC.Stack (CallStack, HasCallStack, SrcLoc (..), getCallStack)
import Lens.Micro
import Prettyprinter (
Doc,
Pretty (..),
Expand Down Expand Up @@ -97,6 +98,12 @@ deriving instance (Eq (ImpSpecEnv t), Eq (ImpSpecState t)) => Eq (ImpInit t)
deriving instance (Ord (ImpSpecEnv t), Ord (ImpSpecState t)) => Ord (ImpInit t)
deriving instance (Show (ImpSpecEnv t), Show (ImpSpecState t)) => Show (ImpInit t)

impInitEnvL :: Lens' (ImpInit t) (ImpSpecEnv t)
impInitEnvL = lens impInitEnv $ \x y -> x {impInitEnv = y}

impInitStateL :: Lens' (ImpInit t) (ImpSpecState t)
impInitStateL = lens impInitState $ \x y -> x {impInitState = y}

-- | Stores extra information about the failure of the unit test
data ImpException = ImpException
{ ieAnnotation :: [Doc AnsiStyle]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,13 @@ library
exposed-modules:
Test.Cardano.Ledger.Conformance
Test.Cardano.Ledger.Conformance.ExecSpecRule.Core
Test.Cardano.Ledger.Conformance.SpecTranslate.Core
Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway
Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Base
Test.Cardano.Ledger.Conformance.SpecTranslate.Conway

hs-source-dirs: src
other-modules:
Test.Cardano.Ledger.Conformance.SpecTranslate.Core
Test.Cardano.Ledger.Conformance.SpecTranslate.Conway.Base
Test.Cardano.Ledger.Conformance.SpecTranslate.Conway.Deleg
Test.Cardano.Ledger.Conformance.SpecTranslate.Conway.Pool
Expand Down Expand Up @@ -106,6 +106,7 @@ test-suite tests
Test.Cardano.Ledger.Conformance.Spec.Conway
Test.Cardano.Ledger.Conformance.ExecSpecRule.MiniTrace
Test.Cardano.Ledger.Conformance.Imp.Ratify
Test.Cardano.Ledger.Conformance.Imp

default-language: Haskell2010
ghc-options:
Expand All @@ -116,14 +117,18 @@ test-suite tests
build-depends:
base >=4.14 && <5,
containers,
data-default,
cardano-data,
constrained-generators,
small-steps,
cardano-ledger-binary,
cardano-ledger-conformance,
cardano-ledger-core:{cardano-ledger-core, testlib},
cardano-strict-containers,
cardano-ledger-shelley,
cardano-ledger-alonzo,
cardano-ledger-conway:{cardano-ledger-conway, testlib},
cardano-ledger-test,
microlens
microlens,
microlens-mtl,
unliftio
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway (
module X,
ConwayRatifyExecContext (..),
ConwayLedgerExecContext (..),
) where

import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Base as X (
Expand All @@ -16,7 +17,9 @@ import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Certs as X (nameCerts
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Deleg as X (nameDelegCert)
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Gov as X ()
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.GovCert as X (nameGovCert)
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Ledger as X ()
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Ledger as X (
ConwayLedgerExecContext (..),
)
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Ledgers as X ()
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Pool as X (namePoolCert)
import Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Utxo as X ()
Expand Down
Loading