cardano-ledger-conformance-9.9.9.9: Testing utilities for conformance testing
Safe HaskellNone
LanguageHaskell2010

Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Synopsis

Documentation

class (ShelleyEraImp era, STS (EraRule rule era), BaseM (EraRule rule era) ~ ShelleyBase, KnownSymbol rule, ForAllExecSpecRep NFData rule era, ForAllExecSpecRep ToExpr rule era, ForAllExecTypes NFData rule era, ForAllExecTypes ToExpr rule era, ForAllExecTypes EncCBOR rule era, EncCBOR (ExecContext rule era), Eq (SpecState rule era), SpecNormalize (SpecState rule era), NFData (ExecContext rule era), NFData (PredicateFailure (EraRule rule era)), NFData (SpecTRC rule era), ToExpr (ExecContext rule era), ToExpr (PredicateFailure (EraRule rule era))) ⇒ ExecSpecRule (rule ∷ Symbol) era where Source #

Minimal complete definition

Nothing

Associated Types

type ExecContext (rule ∷ Symbol) era Source #

type ExecContext (rule ∷ Symbol) era = ()

type SpecEnvironment (rule ∷ Symbol) era Source #

type SpecEnvironment (rule ∷ Symbol) era = SpecRep (Environment (EraRule rule era))

type SpecState (rule ∷ Symbol) era Source #

type SpecState (rule ∷ Symbol) era = SpecRep (State (EraRule rule era))

type SpecSignal (rule ∷ Symbol) era Source #

type SpecSignal (rule ∷ Symbol) era = SpecRep (Signal (EraRule rule era))

Methods

runAgdaRuleSpecTRC rule era → Either Text (SpecState rule era) Source #

runAgdaRuleWithDebugSpecTRC rule era → Either Text (SpecState rule era, Text) Source #

translateInputsExecContext rule era → TRC (EraRule rule era) → Either Text (SpecTRC rule era) Source #

default translateInputs ∷ (SpecTranslate (ExecContext rule era) (Environment (EraRule rule era)), SpecTranslate (ExecContext rule era) (State (EraRule rule era)), SpecTranslate (ExecContext rule era) (Signal (EraRule rule era)), SpecRep (Environment (EraRule rule era)) ~ SpecEnvironment rule era, SpecRep (State (EraRule rule era)) ~ SpecState rule era, SpecRep (Signal (EraRule rule era)) ~ SpecSignal rule era) ⇒ ExecContext rule era → TRC (EraRule rule era) → Either Text (SpecTRC rule era) Source #

translateOutputExecContext rule era → TRC (EraRule rule era) → State (EraRule rule era) → Either Text (SpecState rule era) Source #

default translateOutput ∷ (SpecTranslate (ExecContext rule era) (State (EraRule rule era)), SpecRep (State (EraRule rule era)) ~ SpecState rule era) ⇒ ExecContext rule era → TRC (EraRule rule era) → State (EraRule rule era) → Either Text (SpecState rule era) Source #

extraInfoGlobalsExecContext rule era → TRC (EraRule rule era) → Either Text (State (EraRule rule era), [Event (EraRule rule era)]) → Doc AnsiStyle Source #

Instances

Instances details
ExecSpecRule "CERT" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Cert

ExecSpecRule "CERTS" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Certs

ExecSpecRule "DELEG" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Deleg

ExecSpecRule "ENACT" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Enact

ExecSpecRule "EPOCH" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Epoch

ExecSpecRule "GOV" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Gov

ExecSpecRule "GOVCERT" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.GovCert

Methods

runAgdaRuleSpecTRC "GOVCERT" ConwayEraEither Text (SpecState "GOVCERT" ConwayEra) Source #

runAgdaRuleWithDebugSpecTRC "GOVCERT" ConwayEraEither Text (SpecState "GOVCERT" ConwayEra, Text) Source #

translateInputsExecContext "GOVCERT" ConwayEraTRC (EraRule "GOVCERT" ConwayEra) → Either Text (SpecTRC "GOVCERT" ConwayEra) Source #

translateOutputExecContext "GOVCERT" ConwayEraTRC (EraRule "GOVCERT" ConwayEra) → State (EraRule "GOVCERT" ConwayEra) → Either Text (SpecState "GOVCERT" ConwayEra) Source #

extraInfoGlobalsExecContext "GOVCERT" ConwayEraTRC (EraRule "GOVCERT" ConwayEra) → Either Text (State (EraRule "GOVCERT" ConwayEra), [Event (EraRule "GOVCERT" ConwayEra)]) → Doc AnsiStyle Source #

ExecSpecRule "LEDGER" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Ledger

ExecSpecRule "LEDGERS" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Ledgers

Methods

runAgdaRuleSpecTRC "LEDGERS" ConwayEraEither Text (SpecState "LEDGERS" ConwayEra) Source #

runAgdaRuleWithDebugSpecTRC "LEDGERS" ConwayEraEither Text (SpecState "LEDGERS" ConwayEra, Text) Source #

translateInputsExecContext "LEDGERS" ConwayEraTRC (EraRule "LEDGERS" ConwayEra) → Either Text (SpecTRC "LEDGERS" ConwayEra) Source #

translateOutputExecContext "LEDGERS" ConwayEraTRC (EraRule "LEDGERS" ConwayEra) → State (EraRule "LEDGERS" ConwayEra) → Either Text (SpecState "LEDGERS" ConwayEra) Source #

extraInfoGlobalsExecContext "LEDGERS" ConwayEraTRC (EraRule "LEDGERS" ConwayEra) → Either Text (State (EraRule "LEDGERS" ConwayEra), [Event (EraRule "LEDGERS" ConwayEra)]) → Doc AnsiStyle Source #

ExecSpecRule "NEWEPOCH" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.NewEpoch

Associated Types

type ExecContext "NEWEPOCH" ConwayEra 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.NewEpoch

type ExecContext "NEWEPOCH" ConwayEra = ()
type SpecEnvironment "NEWEPOCH" ConwayEra 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.NewEpoch

type SpecState "NEWEPOCH" ConwayEra 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.NewEpoch

type SpecState "NEWEPOCH" ConwayEra = SpecRep (State (EraRule "NEWEPOCH" ConwayEra))
type SpecSignal "NEWEPOCH" ConwayEra 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.NewEpoch

type SpecSignal "NEWEPOCH" ConwayEra = SpecRep (Signal (EraRule "NEWEPOCH" ConwayEra))

Methods

runAgdaRuleSpecTRC "NEWEPOCH" ConwayEraEither Text (SpecState "NEWEPOCH" ConwayEra) Source #

runAgdaRuleWithDebugSpecTRC "NEWEPOCH" ConwayEraEither Text (SpecState "NEWEPOCH" ConwayEra, Text) Source #

translateInputsExecContext "NEWEPOCH" ConwayEraTRC (EraRule "NEWEPOCH" ConwayEra) → Either Text (SpecTRC "NEWEPOCH" ConwayEra) Source #

translateOutputExecContext "NEWEPOCH" ConwayEraTRC (EraRule "NEWEPOCH" ConwayEra) → State (EraRule "NEWEPOCH" ConwayEra) → Either Text (SpecState "NEWEPOCH" ConwayEra) Source #

extraInfoGlobalsExecContext "NEWEPOCH" ConwayEraTRC (EraRule "NEWEPOCH" ConwayEra) → Either Text (State (EraRule "NEWEPOCH" ConwayEra), [Event (EraRule "NEWEPOCH" ConwayEra)]) → Doc AnsiStyle Source #

ExecSpecRule "POOL" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Pool

ExecSpecRule "RATIFY" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Ratify

ExecSpecRule "UTXO" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Utxo

SpecTranslate TxId (ConwayTxCert ConwayEra) ⇒ ExecSpecRule "UTXOW" ConwayEra Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Conway.Utxow

data ConformanceResult (rule ∷ Symbol) era Source #

Instances

Instances details
Generic (ConformanceResult rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Associated Types

type Rep (ConformanceResult rule era) 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

type Rep (ConformanceResult rule era) = D1 ('MetaData "ConformanceResult" "Test.Cardano.Ledger.Conformance.ExecSpecRule.Core" "cardano-ledger-conformance-9.9.9.9-inplace" 'False) (C1 ('MetaCons "ConformanceResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "crTranslationResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (NonEmpty (PredicateFailure (EraRule rule era))) (SpecState rule era))) :*: (S1 ('MetaSel ('Just "crSpecificationResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either Text (SpecState rule era))) :*: S1 ('MetaSel ('Just "crImplementationResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (NonEmpty (PredicateFailure (EraRule rule era))) (State (EraRule rule era), [Event (EraRule rule era)]))))))

Methods

fromConformanceResult rule era → Rep (ConformanceResult rule era) x #

toRep (ConformanceResult rule era) x → ConformanceResult rule era #

(Show (SpecState rule era), Show (PredicateFailure (EraRule rule era)), Show (State (EraRule rule era)), Show (Event (EraRule rule era))) ⇒ Show (ConformanceResult rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Methods

showsPrecIntConformanceResult rule era → ShowS #

showConformanceResult rule era → String #

showList ∷ [ConformanceResult rule era] → ShowS #

(ToExpr (SpecState rule era), ToExpr (PredicateFailure (EraRule rule era)), ToExpr (State (EraRule rule era)), ToExpr (Event (EraRule rule era))) ⇒ ToExpr (ConformanceResult rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Methods

toExprConformanceResult rule era → Expr Source #

listToExpr ∷ [ConformanceResult rule era] → Expr Source #

type Rep (ConformanceResult rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

type Rep (ConformanceResult rule era) = D1 ('MetaData "ConformanceResult" "Test.Cardano.Ledger.Conformance.ExecSpecRule.Core" "cardano-ledger-conformance-9.9.9.9-inplace" 'False) (C1 ('MetaCons "ConformanceResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "crTranslationResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (NonEmpty (PredicateFailure (EraRule rule era))) (SpecState rule era))) :*: (S1 ('MetaSel ('Just "crSpecificationResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either Text (SpecState rule era))) :*: S1 ('MetaSel ('Just "crImplementationResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (NonEmpty (PredicateFailure (EraRule rule era))) (State (EraRule rule era), [Event (EraRule rule era)]))))))

data SpecTRC (rule ∷ Symbol) era Source #

Constructors

SpecTRC 

Fields

Instances

Instances details
ForAllExecSpecRep NFData rule era ⇒ NFData (SpecTRC rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Methods

rnfSpecTRC rule era → () #

Generic (SpecTRC rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Associated Types

type Rep (SpecTRC rule era) 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

type Rep (SpecTRC rule era) = D1 ('MetaData "SpecTRC" "Test.Cardano.Ledger.Conformance.ExecSpecRule.Core" "cardano-ledger-conformance-9.9.9.9-inplace" 'False) (C1 ('MetaCons "SpecTRC" 'PrefixI 'True) (S1 ('MetaSel ('Just "strcEnvironment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecEnvironment rule era)) :*: (S1 ('MetaSel ('Just "strcState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecState rule era)) :*: S1 ('MetaSel ('Just "strcSignal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecSignal rule era)))))

Methods

fromSpecTRC rule era → Rep (SpecTRC rule era) x #

toRep (SpecTRC rule era) x → SpecTRC rule era #

ForAllExecSpecRep Eq rule era ⇒ Eq (SpecTRC rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Methods

(==)SpecTRC rule era → SpecTRC rule era → Bool #

(/=)SpecTRC rule era → SpecTRC rule era → Bool #

ForAllExecSpecRep ToExpr rule era ⇒ ToExpr (SpecTRC rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

Methods

toExprSpecTRC rule era → Expr Source #

listToExpr ∷ [SpecTRC rule era] → Expr Source #

type Rep (SpecTRC rule era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Conformance.ExecSpecRule.Core

type Rep (SpecTRC rule era) = D1 ('MetaData "SpecTRC" "Test.Cardano.Ledger.Conformance.ExecSpecRule.Core" "cardano-ledger-conformance-9.9.9.9-inplace" 'False) (C1 ('MetaCons "SpecTRC" 'PrefixI 'True) (S1 ('MetaSel ('Just "strcEnvironment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecEnvironment rule era)) :*: (S1 ('MetaSel ('Just "strcState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecState rule era)) :*: S1 ('MetaSel ('Just "strcSignal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SpecSignal rule era)))))

runConformance ∷ ∀ (rule ∷ Symbol) era. ExecSpecRule rule era ⇒ ExecContext rule era → TRC (EraRule rule era) → ImpTestM era (ConformanceResult rule era) Source #

checkConformance ∷ ∀ (rule ∷ Symbol) era. (HasCallStack, Era era, EncCBOR (ExecContext rule era), EncCBOR (Environment (EraRule rule era)), EncCBOR (State (EraRule rule era)), EncCBOR (Signal (EraRule rule era)), ToExpr (SpecState rule era), Eq (SpecState rule era), SpecNormalize (SpecState rule era)) ⇒ ExecContext rule era → TRC (EraRule rule era) → Either Text (SpecState rule era) → Either Text (SpecState rule era) → ImpTestM era () Source #

testConformance ∷ ∀ (rule ∷ Symbol) era. (HasCallStack, ExecSpecRule rule era) ⇒ ExecContext rule era → TRC (EraRule rule era) → Property Source #

translateWithContextSpecTranslate ctx a ⇒ ctx → a → ImpTestM era (Either Text (SpecRep a)) Source #

Translate a Haskell type a whose translation context is ctx into its Agda type, in the ImpTest monad.

type ForAllExecSpecRep (c ∷ TypeConstraint) (rule ∷ Symbol) era = (c (SpecEnvironment rule era), c (SpecState rule era), c (SpecSignal rule era)) Source #

type ForAllExecTypes (c ∷ TypeConstraint) (rule ∷ Symbol) era = (c (Environment (EraRule rule era)), c (State (EraRule rule era)), c (Signal (EraRule rule era))) Source #

runFromAgdaFunction ∷ ∀ (rule ∷ Symbol) era. (SpecEnvironment rule era → SpecState rule era → SpecSignal rule era → ComputationResult Text (SpecState rule era)) → SpecTRC rule era → Either Text (SpecState rule era) Source #