cardano-ledger-shelley-1.16.0.0: Shelley Ledger Executable Model
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cardano.Ledger.Shelley.ImpTest

Synopsis

Documentation

type ImpTestM era = ImpM (LedgerSpec era) Source #

data LedgerSpec era Source #

Instances

Instances details
ShelleyEraImp era ⇒ ImpSpec (LedgerSpec era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

Associated Types

type ImpSpecEnv (LedgerSpec era) = (r ∷ Type) Source #

type ImpSpecState (LedgerSpec era) = (r ∷ Type) Source #

Methods

impInitIO ∷ QCGen → IO (ImpInit (LedgerSpec era)) Source #

impPrepActionImpM (LedgerSpec era) () Source #

MonadWriter [SomeSTSEvent era] (ImpTestM era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

Methods

writer ∷ (a, [SomeSTSEvent era]) → ImpTestM era a Source #

tell ∷ [SomeSTSEvent era] → ImpTestM era () Source #

listenImpTestM era a → ImpTestM era (a, [SomeSTSEvent era]) Source #

passImpTestM era (a, [SomeSTSEvent era] → [SomeSTSEvent era]) → ImpTestM era a Source #

type ImpSpecEnv (LedgerSpec era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

type ImpSpecState (LedgerSpec era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

data SomeSTSEvent era Source #

Constructors

∀ (rule ∷ Symbol).(Typeable (Event (EraRule rule era)), Eq (Event (EraRule rule era)), ToExpr (Event (EraRule rule era))) ⇒ SomeSTSEvent (Event (EraRule rule era)) 

Instances

Instances details
Eq (SomeSTSEvent era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

Methods

(==)SomeSTSEvent era → SomeSTSEvent era → Bool Source #

(/=)SomeSTSEvent era → SomeSTSEvent era → Bool Source #

ToExpr (SomeSTSEvent era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

MonadWriter [SomeSTSEvent era] (ImpTestM era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

Methods

writer ∷ (a, [SomeSTSEvent era]) → ImpTestM era a Source #

tell ∷ [SomeSTSEvent era] → ImpTestM era () Source #

listenImpTestM era a → ImpTestM era (a, [SomeSTSEvent era]) Source #

passImpTestM era (a, [SomeSTSEvent era] → [SomeSTSEvent era]) → ImpTestM era a Source #

data ImpTestEnv era Source #

Constructors

ImpTestEnv 

Fields

data ImpException Source #

Stores extra information about the failure of the unit test

Constructors

ImpException 

Fields

class (EraGov era, EraUTxO era, EraTxOut era, EraPParams era, ShelleyEraTxCert era, ShelleyEraScript era, ToExpr (Tx era), NFData (Tx era), ToExpr (TxBody era), ToExpr (TxOut era), ToExpr (Value era), ToExpr (PParams era), ToExpr (PParamsHKD Identity era), ToExpr (PParamsHKD StrictMaybe era), Show (NewEpochState era), ToExpr (NewEpochState era), ToExpr (GovState era), Eq (StashedAVVMAddresses era), Show (StashedAVVMAddresses era), ToExpr (StashedAVVMAddresses era), NFData (StashedAVVMAddresses era), Default (StashedAVVMAddresses era), STS (EraRule "BBODY" era), BaseM (EraRule "BBODY" era) ~ ShelleyBase, Environment (EraRule "BBODY" era) ~ BbodyEnv era, State (EraRule "BBODY" era) ~ ShelleyBbodyState era, Signal (EraRule "BBODY" era) ~ Block BHeaderView era, State (EraRule "LEDGERS" era) ~ LedgerState era, STS (EraRule "LEDGER" era), BaseM (EraRule "LEDGER" era) ~ ShelleyBase, Signal (EraRule "LEDGER" era) ~ Tx era, State (EraRule "LEDGER" era) ~ LedgerState era, Environment (EraRule "LEDGER" era) ~ LedgerEnv era, Eq (PredicateFailure (EraRule "LEDGER" era)), Show (PredicateFailure (EraRule "LEDGER" era)), ToExpr (PredicateFailure (EraRule "LEDGER" era)), NFData (PredicateFailure (EraRule "LEDGER" era)), EncCBOR (PredicateFailure (EraRule "LEDGER" era)), DecCBOR (PredicateFailure (EraRule "LEDGER" era)), EraRuleEvent "LEDGER" era ~ Event (EraRule "LEDGER" era), Eq (EraRuleEvent "LEDGER" era), ToExpr (EraRuleEvent "LEDGER" era), NFData (EraRuleEvent "LEDGER" era), Typeable (EraRuleEvent "LEDGER" era), STS (EraRule "TICK" era), BaseM (EraRule "TICK" era) ~ ShelleyBase, Signal (EraRule "TICK" era) ~ SlotNo, State (EraRule "TICK" era) ~ NewEpochState era, Environment (EraRule "TICK" era) ~ (), NFData (PredicateFailure (EraRule "TICK" era)), EraRuleEvent "TICK" era ~ Event (EraRule "TICK" era), Eq (EraRuleEvent "TICK" era), ToExpr (EraRuleEvent "TICK" era), NFData (EraRuleEvent "TICK" era), Typeable (EraRuleEvent "TICK" era), ToExpr (PredicateFailure (EraRule "UTXOW" era))) ⇒ ShelleyEraImp era where Source #

Minimal complete definition

impSatisfyNativeScript, fixupTx

Methods

initGenesis ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m, MonadFail m) ⇒ m (Genesis era) Source #

default initGenesis ∷ (Monad m, Genesis era ~ NoGenesis era) ⇒ m (Genesis era) Source #

initNewEpochState ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m, MonadFail m) ⇒ m (NewEpochState era) Source #

initImpTestState ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m, MonadFail m) ⇒ m (ImpTestState era) Source #

impSatisfyNativeScript Source #

Arguments

Set (KeyHash 'Witness)

Set of Witnesses that have already been satisfied

TxBody era

The transaction body that the script will be applied to

NativeScript era 
ImpTestM era (Maybe (Map (KeyHash 'Witness) (KeyPair 'Witness))) 

Try to find a sufficient number of KeyPairs that would satisfy a native script. Whenever script can't be satisfied, Nothing is returned

modifyPParams ∷ (PParams era → PParams era) → ImpTestM era () Source #

This modifer should change not only the current PParams, but also the future PParams. If the future PParams are not updated, then they will overwrite the mofication of the current PParams at the next epoch.

fixupTxHasCallStackTx era → ImpTestM era (Tx era) Source #

data PlutusArgs Source #

Instances

Instances details
Generic PlutusArgs 
Instance details

Defined in Test.Cardano.Ledger.Plutus.ScriptTestContext

Associated Types

type Rep PlutusArgsTypeType Source #

Show PlutusArgs 
Instance details

Defined in Test.Cardano.Ledger.Plutus.ScriptTestContext

NFData PlutusArgs 
Instance details

Defined in Test.Cardano.Ledger.Plutus.ScriptTestContext

Methods

rnfPlutusArgs → () Source #

type Rep PlutusArgs 
Instance details

Defined in Test.Cardano.Ledger.Plutus.ScriptTestContext

type Rep PlutusArgs = D1 ('MetaData "PlutusArgs" "Test.Cardano.Ledger.Plutus.ScriptTestContext" "cardano-ledger-core-1.17.0.0-inplace-testlib" 'False) (C1 ('MetaCons "PlutusArgs" 'PrefixI 'True) (S1 ('MetaSel ('Just "paData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Data) :*: S1 ('MetaSel ('Just "paSpendDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Data))))

impWitsVKeyNeededEraUTxO era ⇒ TxBody era → ImpTestM era (Set BootstrapAddress, Set (KeyHash 'Witness)) Source #

Figure out all the Byron Addresses that need witnesses as well as all of the KeyHashes for Shelley Key witnesses that are required.

modifyPrevPParamsEraGov era ⇒ (PParams era → PParams era) → ImpTestM era () Source #

Modify the previous PParams in the current state with the given function. For current and future PParams, use modifyPParams

passEpoch ∷ ∀ era. (ShelleyEraImp era, HasCallStack) ⇒ ImpTestM era () Source #

Runs the TICK rule until the next epoch is reached

passNEpochs ∷ ∀ era. ShelleyEraImp era ⇒ NaturalImpTestM era () Source #

Runs the TICK rule until the n epochs are passed

passNEpochsChecking ∷ ∀ era. ShelleyEraImp era ⇒ NaturalImpTestM era () → ImpTestM era () Source #

Runs the TICK rule until the n epochs are passed, running the checks each time.

passTick ∷ ∀ era. (HasCallStack, ShelleyEraImp era) ⇒ ImpTestM era () Source #

Runs the TICK rule once

freshKeyAddr ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m) ⇒ m (KeyHash r, Addr) Source #

Generate a random Addr that uses a KeyHash, add the corresponding KeyPair to the known keys in the Imp state, and return the KeyHash as well as the Addr.

freshKeyAddr_ ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m) ⇒ m Addr Source #

Generate a random Addr that uses a KeyHash, and add the corresponding KeyPair to the known keys in the Imp state.

freshKeyHash ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m) ⇒ m (KeyHash r) Source #

Generates a fresh KeyHash and stores the corresponding KeyPair in the ImpTestState. If you also need the KeyPair consider using freshKeyPair for generation or lookupKeyPair to look up the KeyPair corresponding to the KeyHash

freshKeyPair ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m) ⇒ m (KeyHash r, KeyPair r) Source #

Generate a random KeyPair and add it to the known keys in the Imp state

lookupKeyPair ∷ (HasCallStack, HasKeyPairs s, MonadState s m) ⇒ KeyHash r → m (KeyPair r) Source #

Looks up the KeyPair corresponding to the KeyHash. The KeyHash must be created with freshKeyHash for this to work.

freshByronKeyHash ∷ (HasKeyPairs s, MonadState s m, HasStatefulGen g m) ⇒ m (KeyHash r) Source #

Generates a fresh KeyHash and stores the corresponding ByronKeyPair in the ImpTestState. If you also need the ByronKeyPair consider using freshByronKeyPair for generation or lookupByronKeyPair to look up the ByronKeyPair corresponding to the KeyHash

lookupByronKeyPair ∷ (HasCallStack, HasKeyPairs s, MonadState s m) ⇒ BootstrapAddress → m ByronKeyPair Source #

Looks up the keypair corresponding to the BootstrapAddress. The BootstrapAddress must be created with freshBootstrapAddess for this to work.

freshSafeHashImpTestM era (SafeHash a) Source #

Creates a fresh SafeHash

submitTx ∷ (HasCallStack, ShelleyEraImp era) ⇒ Tx era → ImpTestM era (Tx era) Source #

submitTx_ ∷ (HasCallStack, ShelleyEraImp era) ⇒ Tx era → ImpTestM era () Source #

submitTxAnn ∷ (HasCallStack, ShelleyEraImp era) ⇒ StringTx era → ImpTestM era (Tx era) Source #

submitTxAnn_ ∷ (HasCallStack, ShelleyEraImp era) ⇒ StringTx era → ImpTestM era () Source #

submitFailingTx ∷ (HasCallStack, ShelleyEraImp era) ⇒ Tx era → NonEmpty (PredicateFailure (EraRule "LEDGER" era)) → ImpTestM era () Source #

Submit a transaction that is expected to be rejected with the given predicate failures. The inputs and outputs are automatically balanced.

submitFailingTxM ∷ (HasCallStack, ShelleyEraImp era) ⇒ Tx era → (Tx era → ImpTestM era (NonEmpty (PredicateFailure (EraRule "LEDGER" era)))) → ImpTestM era () Source #

Submit a transaction that is expected to be rejected, and compute the expected predicate failures from the fixed-up tx using the supplied action. The inputs and outputs are automatically balanced.

trySubmitTx ∷ ∀ era. (ShelleyEraImp era, HasCallStack) ⇒ Tx era → ImpTestM era (Either (NonEmpty (PredicateFailure (EraRule "LEDGER" era)), Tx era) (Tx era)) Source #

modifyNES ∷ (NewEpochState era → NewEpochState era) → ImpTestM era () Source #

Modify the current new epoch state with a function

getsNESSimpleGetter (NewEpochState era) a → ImpTestM era a Source #

Get a value from the current new epoch state using the lens

getUTxOImpTestM era (UTxO era) Source #

impAnnNFData a ⇒ StringImpM t a → ImpM t a Source #

Annotation for when failure happens. All the logging done within annotation will be discarded if there no failures within the annotation.

impAnnDocNFData a ⇒ Doc AnsiStyleImpM t a → ImpM t a Source #

impLogToExpr ∷ (HasCallStack, ToExpr a) ⇒ ImpTestM era a → ImpTestM era a Source #

Adds the result of an action to the log, which is only shown if the test fails

runImpRule ∷ ∀ rule era. (HasCallStack, KnownSymbol rule, STS (EraRule rule era), BaseM (EraRule rule era) ~ ShelleyBase, NFData (State (EraRule rule era)), NFData (Event (EraRule rule era)), ToExpr (Event (EraRule rule era)), Eq (Event (EraRule rule era)), Typeable (Event (EraRule rule era))) ⇒ Environment (EraRule rule era) → State (EraRule rule era) → Signal (EraRule rule era) → ImpTestM era (State (EraRule rule era)) Source #

tryRunImpRule ∷ ∀ rule era. (STS (EraRule rule era), BaseM (EraRule rule era) ~ ShelleyBase) ⇒ Environment (EraRule rule era) → State (EraRule rule era) → Signal (EraRule rule era) → ImpTestM era (Either (NonEmpty (PredicateFailure (EraRule rule era))) (State (EraRule rule era), [Event (EraRule rule era)])) Source #

tryRunImpRuleNoAssertions ∷ ∀ rule era. (STS (EraRule rule era), BaseM (EraRule rule era) ~ ShelleyBase) ⇒ Environment (EraRule rule era) → State (EraRule rule era) → Signal (EraRule rule era) → ImpTestM era (Either (NonEmpty (PredicateFailure (EraRule rule era))) (State (EraRule rule era), [Event (EraRule rule era)])) Source #

shelleyFixupTx ∷ ∀ era. (ShelleyEraImp era, HasCallStack) ⇒ Tx era → ImpTestM era (Tx era) Source #

expectUTxOContent ∷ (HasCallStack, ToExpr (TxOut era)) ⇒ UTxO era → [(TxIn, Maybe (TxOut era) → Bool)] → ImpTestM era () Source #

updateAddrTxWits ∷ (HasCallStack, ShelleyEraImp era) ⇒ Tx era → ImpTestM era (Tx era) Source #

Adds TxWits that will satisfy all of the required key witnesses

addNativeScriptTxWitsShelleyEraImp era ⇒ Tx era → ImpTestM era (Tx era) Source #

Modifies transaction by adding necessary scripts

addRootTxInShelleyEraImp era ⇒ Tx era → ImpTestM era (Tx era) Source #

This fixup step ensures that there are enough funds in the transaction.

fixupTxOuts ∷ (ShelleyEraImp era, HasCallStack) ⇒ Tx era → ImpTestM era (Tx era) Source #

fixupFees ∷ (ShelleyEraImp era, HasCallStack) ⇒ Tx era → ImpTestM era (Tx era) Source #

fixupAuxDataHash ∷ (EraTx era, Applicative m) ⇒ Tx era → m (Tx era) Source #

Adds an auxiliary data hash if auxiliary data present, while the hash of it is not.

defaultInitImpTestState ∷ ∀ era s g m. (EraGov era, EraTxOut era, HasKeyPairs s, MonadState s m, HasStatefulGen g m, MonadFail m) ⇒ NewEpochState era → m (ImpTestState era) Source #

impEraStartEpochNo ∷ ∀ era. Era era ⇒ EpochNo Source #

For debugging purposes we start the era at the epoch number that matches the starting protocol version for the era times a 100

impSetSeedIntImpM t () Source #

Override the QuickCheck generator using a fixed seed.

modifyImpInitExpectLedgerRuleConformance ∷ ∀ era. (GlobalsEither (NonEmpty (PredicateFailure (EraRule "LEDGER" era))) (State (EraRule "LEDGER" era), [Event (EraRule "LEDGER" era)]) → LedgerEnv era → LedgerState era → Tx era → BaseImpM ()) → SpecWith (ImpInit (LedgerSpec era)) → SpecWith (ImpInit (LedgerSpec era)) Source #

Logging

data Doc ann Source #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann.

More specifically, a value of type Doc represents a non-empty set of possible layouts of a document. The layout functions select one of these possibilities, taking into account things like the width of the output document.

The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as

  • color information (e.g. when rendering to the terminal)
  • mouseover text (e.g. when rendering to rich HTML)
  • whether to show something or not (to allow simple or detailed versions)

The simplest way to display a Doc is via the Show class.

>>> putStrLn (show (vsep ["hello", "world"]))
hello
world

Instances

Instances details
Functor Doc

Alter the document’s annotations.

This instance makes Doc more flexible (because it can be used in Functor-polymorphic values), but fmap is much less readable compared to using reAnnotate in code that only works for Doc anyway. Consider using the latter when the type does not matter.

Instance details

Defined in Prettyprinter.Internal

Methods

fmap ∷ (a → b) → Doc a → Doc b Source #

(<$) ∷ a → Doc b → Doc a Source #

IsString (Doc ann)
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Doc instance, and uses the same newline to line conversion.

Instance details

Defined in Prettyprinter.Internal

Methods

fromStringStringDoc ann Source #

Monoid (Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Methods

memptyDoc ann Source #

mappendDoc ann → Doc ann → Doc ann Source #

mconcat ∷ [Doc ann] → Doc ann Source #

Semigroup (Doc ann)
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Methods

(<>)Doc ann → Doc ann → Doc ann Source #

sconcatNonEmpty (Doc ann) → Doc ann Source #

stimesIntegral b ⇒ b → Doc ann → Doc ann Source #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) ∷ TypeType Source #

Methods

fromDoc ann → Rep (Doc ann) x Source #

toRep (Doc ann) x → Doc ann Source #

Show (Doc ann)

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Instance details

Defined in Prettyprinter.Internal

Methods

showsPrecIntDoc ann → ShowS Source #

showDoc ann → String Source #

showList ∷ [Doc ann] → ShowS Source #

type Rep (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

type Rep (Doc ann) = D1 ('MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-60fc2444dcacdd48cc73f93e5ef87c40fa69faa308b0e641b05323137692b85e" 'False) (((C1 ('MetaCons "Fail" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Char)))) :+: (C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Line" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "FlatAlt" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 ('MetaCons "Cat" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: (C1 ('MetaCons "Nest" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntDoc ann))) :+: C1 ('MetaCons "WithPageWidth" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PageWidthDoc ann)))) :+: (C1 ('MetaCons "Nesting" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntDoc ann))) :+: C1 ('MetaCons "Annotated" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))))

data AnsiStyle Source #

Render the annotated document in a certain style. Styles not set in the annotation will use the style of the surrounding document, or the terminal’s default if none has been set yet.

style = color Green <> bold
styledDoc = annotate style "hello world"

Instances

Instances details
Monoid AnsiStyle

mempty does nothing, which is equivalent to inheriting the style of the surrounding doc, or the terminal’s default if no style has been set yet.

Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Semigroup AnsiStyle

Keep the first decision for each of foreground color, background color, boldness, italication, and underlining. If a certain style is not set, the terminal’s default will be used.

Example:

color Red <> color Green

is red because the first color wins, and not bold because (or if) that’s the terminal’s default.

Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Show AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Eq AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Ord AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

logDocHasCallStackDoc AnsiStyleImpM t () Source #

Adds a Doc to the log, which is only shown if the test fails

logTextHasCallStackTextImpM t () Source #

Adds a Text to the log, which is only shown if the test fails

logStringHasCallStackStringImpM t () Source #

Adds a String to the log, which is only shown if the test fails

logToExpr ∷ (HasCallStack, ToExpr a) ⇒ a → ImpM t () Source #

Adds a ToExpr to the log, which is only shown if the test fails

logStakeDistrHasCallStackImpTestM era () Source #

Logs the current stake distribution

logFeeMismatch ∷ (EraGov era, EraUTxO era, HasCallStack) ⇒ Tx era → ImpTestM era () Source #

Combinators

withCustomFixup ∷ ((Tx era → ImpTestM era (Tx era)) → Tx era → ImpTestM era (Tx era)) → ImpTestM era a → ImpTestM era a Source #

Compose given function with the configured fixup

withFixup ∷ (Tx era → ImpTestM era (Tx era)) → ImpTestM era a → ImpTestM era a Source #

Replace all fixup with the given function

withNoFixupImpTestM era a → ImpTestM era a Source #

Performs the action without running the fix-up function on any transactions

withPostFixup ∷ (Tx era → ImpTestM era (Tx era)) → ImpTestM era a → ImpTestM era a Source #

Apply given fixup function after the configured fixup

withPreFixup ∷ (Tx era → ImpTestM era (Tx era)) → ImpTestM era a → ImpTestM era a Source #

Apply given fixup function before the configured fixup

ImpSpec re-exports

data ImpM t a Source #

Instances

Instances details
env ~ ImpSpecEnv t ⇒ MonadReader env (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

askImpM t env Source #

local ∷ (env → env) → ImpM t a → ImpM t a Source #

reader ∷ (env → a) → ImpM t a Source #

s ~ ImpSpecState t ⇒ MonadState s (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

getImpM t s Source #

put ∷ s → ImpM t () Source #

state ∷ (s → (a, s)) → ImpM t a Source #

MonadFail (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

failStringImpM t a Source #

MonadIO (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

liftIOIO a → ImpM t a Source #

Applicative (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

pure ∷ a → ImpM t a Source #

(<*>)ImpM t (a → b) → ImpM t a → ImpM t b Source #

liftA2 ∷ (a → b → c) → ImpM t a → ImpM t b → ImpM t c Source #

(*>)ImpM t a → ImpM t b → ImpM t b Source #

(<*)ImpM t a → ImpM t b → ImpM t a Source #

Functor (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

fmap ∷ (a → b) → ImpM t a → ImpM t b Source #

(<$) ∷ a → ImpM t b → ImpM t a Source #

Monad (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

(>>=)ImpM t a → (a → ImpM t b) → ImpM t b Source #

(>>)ImpM t a → ImpM t b → ImpM t b Source #

return ∷ a → ImpM t a Source #

MonadGen (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

liftGenGen a → ImpM t a Source #

variantIntegral n ⇒ n → ImpM t a → ImpM t a Source #

sized ∷ (IntImpM t a) → ImpM t a Source #

resizeIntImpM t a → ImpM t a Source #

chooseRandom a ⇒ (a, a) → ImpM t a Source #

MonadUnliftIO (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

withRunInIO ∷ ((∀ a. ImpM t a → IO a) → IO b) → ImpM t b Source #

HasStatefulGen (IOGenM QCGen) (ImpM t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

askStatefulGenImpM t (IOGenM QCGen) Source #

MonadWriter [SomeSTSEvent era] (ImpTestM era) Source # 
Instance details

Defined in Test.Cardano.Ledger.Shelley.ImpTest

Methods

writer ∷ (a, [SomeSTSEvent era]) → ImpTestM era a Source #

tell ∷ [SomeSTSEvent era] → ImpTestM era () Source #

listenImpTestM era a → ImpTestM era (a, [SomeSTSEvent era]) Source #

passImpTestM era (a, [SomeSTSEvent era] → [SomeSTSEvent era]) → ImpTestM era a Source #

(ImpSpec t, Testable a) ⇒ Testable (ImpM t a) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

propertyImpM t a → Property Source #

propertyForAllShrinkShowGen a0 → (a0 → [a0]) → (a0 → [String]) → (a0 → ImpM t a) → Property Source #

(ImpSpec t, Testable p) ⇒ Example (ImpM t p) 
Instance details

Defined in Test.ImpSpec.Internal

Associated Types

type Arg (ImpM t p) Source #

Methods

evaluateExampleImpM t p → Params → (ActionWith (Arg (ImpM t p)) → IO ()) → ProgressCallbackIO Result Source #

(Arbitrary a, Show a, ImpSpec t, Testable p) ⇒ Example (a → ImpM t p) 
Instance details

Defined in Test.ImpSpec.Internal

Associated Types

type Arg (a → ImpM t p) Source #

Methods

evaluateExample ∷ (a → ImpM t p) → Params → (ActionWith (Arg (a → ImpM t p)) → IO ()) → ProgressCallbackIO Result Source #

type Arg (ImpM t p) 
Instance details

Defined in Test.ImpSpec.Internal

type Arg (ImpM t p) = ImpInit t
type Arg (a → ImpM t p) 
Instance details

Defined in Test.ImpSpec.Internal

type Arg (a → ImpM t p) = ImpInit t

data ImpInit t Source #

Instances

Instances details
(Show (ImpSpecEnv t), Show (ImpSpecState t)) ⇒ Show (ImpInit t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

showsPrecIntImpInit t → ShowS Source #

showImpInit t → String Source #

showList ∷ [ImpInit t] → ShowS Source #

(Eq (ImpSpecEnv t), Eq (ImpSpecState t)) ⇒ Eq (ImpInit t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

(==)ImpInit t → ImpInit t → Bool Source #

(/=)ImpInit t → ImpInit t → Bool Source #

(Ord (ImpSpecEnv t), Ord (ImpSpecState t)) ⇒ Ord (ImpInit t) 
Instance details

Defined in Test.ImpSpec.Internal

Methods

compareImpInit t → ImpInit t → Ordering Source #

(<)ImpInit t → ImpInit t → Bool Source #

(<=)ImpInit t → ImpInit t → Bool Source #

(>)ImpInit t → ImpInit t → Bool Source #

(>=)ImpInit t → ImpInit t → Bool Source #

maxImpInit t → ImpInit t → ImpInit t Source #

minImpInit t → ImpInit t → ImpInit t Source #