tests
Safe HaskellSafe-Inferred
LanguageGHC2021

Hydra.Chain.Direct.TxTraceSpec

Description

Stateful model-based testing of the transactions created by the Direct chain modules.

The model is focusing on transitions between Open and Closed states of the head right now. It generates plausible sequences of Decrement and Close actions, along with Contest and Fanout, each using a snapshot of some version and number. UTxOs are simplified such that their identity is A-E and value is just a number.

Actions and snapshots are generated "just-in-time" and result in valid, but also deliberately invalid combinations of versions/numbers. Generated snapshots are correctly signed and consistent in what they decommit from the head.

Synopsis

Documentation

spec :: Spec Source #

prop_traces :: Property Source #

prop_runActions :: Actions Model -> Property Source #

============================== MODEL WORLD ==========================

data SingleUTxO Source #

Constructors

A 
B 
C 
D 
E 

Instances

Instances details
Arbitrary SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Enum SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Generic SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Associated Types

type Rep SingleUTxO :: Type -> Type Source #

Show SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Eq SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Ord SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

type Rep SingleUTxO Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

type Rep SingleUTxO = D1 ('MetaData "SingleUTxO" "Hydra.Chain.Direct.TxTraceSpec" "main" 'False) ((C1 ('MetaCons "A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "B" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "C" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "E" 'PrefixI 'False) (U1 :: Type -> Type))))

data Model Source #

Constructors

Model 

Instances

Instances details
Show Model Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

StateModel Model Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Associated Types

data Action Model a

type Error Model

Methods

actionName :: Action Model a -> String

arbitraryAction :: VarContext -> Model -> Gen (Any (Action Model))

shrinkAction :: Typeable a => VarContext -> Model -> Action Model a -> [Any (Action Model)]

initialState :: Model

nextState :: Typeable a => Model -> Action Model a -> Var a -> Model

failureNextState :: Typeable a => Model -> Action Model a -> Model

precondition :: Model -> Action Model a -> Bool

validFailingAction :: Model -> Action Model a -> Bool

HasVariables Model Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

getAllVariables :: Model -> Set (Any Var)

RunModel Model AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

perform :: Typeable a => Model -> Action Model a -> LookUp AppM -> AppM (PerformResult (Error Model) (Realized AppM a))

postcondition :: (Model, Model) -> Action Model a -> LookUp AppM -> Realized AppM a -> PostconditionM AppM Bool

postconditionOnFailure :: (Model, Model) -> Action Model a -> LookUp AppM -> Either (Error Model) (Realized AppM a) -> PostconditionM AppM Bool

monitoring :: (Model, Model) -> Action Model a -> LookUp AppM -> Either (Error Model) (Realized AppM a) -> Property -> Property

monitoringFailure :: Model -> Action Model a -> LookUp AppM -> Error Model -> Property -> Property

Show (Action Model a) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

showsPrec :: Int -> Action Model a -> ShowS Source #

show :: Action Model a -> String Source #

showList :: [Action Model a] -> ShowS Source #

Eq (Action Model a) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

(==) :: Action Model a -> Action Model a -> Bool Source #

(/=) :: Action Model a -> Action Model a -> Bool Source #

HasVariables (Action Model a) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

getAllVariables :: Action Model a -> Set (Any Var)

data Action Model a Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

data Action Model a where
type Error Model Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

type Error Model = Void

data ModelSnapshot Source #

Model of a real snapshot which contains a SnapshotNumber but also our simplified form of UTxO.

Constructors

ModelSnapshot 

Fields

Instances

Instances details
Arbitrary ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Generic ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Associated Types

type Rep ModelSnapshot :: Type -> Type Source #

Num ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Show ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Eq ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Ord ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

type Rep ModelSnapshot Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

type Rep ModelSnapshot = D1 ('MetaData "ModelSnapshot" "Hydra.Chain.Direct.TxTraceSpec" "main" 'False) (C1 ('MetaCons "ModelSnapshot" 'PrefixI 'True) ((S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SnapshotVersion) :*: S1 ('MetaSel ('Just "number") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SnapshotNumber)) :*: (S1 ('MetaSel ('Just "snapshotUTxO") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModelUTxO) :*: S1 ('MetaSel ('Just "decommitUTxO") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModelUTxO))))

data State Source #

Constructors

Open 
Closed 
Final 

Instances

Instances details
Show State Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Eq State Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

(==) :: State -> State -> Bool Source #

(/=) :: State -> State -> Bool Source #

data Actor Source #

Constructors

Alice 
Bob 
Carol 

Instances

Instances details
Show Actor Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Eq Actor Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

(==) :: Actor -> Actor -> Bool Source #

(/=) :: Actor -> Actor -> Bool Source #

data TxResult Source #

Result of constructing and performing a transaction. Notably there are three stages to this which can fail: construction, validation, and observation. Results from all stages are needed to express post-conditions.

Constructors

TxResult 

Fields

Instances

Instances details
Show TxResult Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Eq TxResult Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

============================== REAL WORLD ==========================

newtype AppM a Source #

Application monad to perform model actions. Currently it only keeps a UTxO which is updated whenever transactions are valid in performTx.

Constructors

AppM 

Fields

Instances

Instances details
MonadFail AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

fail :: String -> AppM a Source #

MonadIO AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

liftIO :: IO a -> AppM a Source #

Applicative AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

pure :: a -> AppM a Source #

(<*>) :: AppM (a -> b) -> AppM a -> AppM b Source #

liftA2 :: (a -> b -> c) -> AppM a -> AppM b -> AppM c Source #

(*>) :: AppM a -> AppM b -> AppM b Source #

(<*) :: AppM a -> AppM b -> AppM a Source #

Functor AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

fmap :: (a -> b) -> AppM a -> AppM b Source #

(<$) :: a -> AppM b -> AppM a Source #

Monad AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

(>>=) :: AppM a -> (a -> AppM b) -> AppM b Source #

(>>) :: AppM a -> AppM b -> AppM b Source #

return :: a -> AppM a Source #

MonadThrow AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

throwIO :: Exception e => e -> AppM a

bracket :: AppM a -> (a -> AppM b) -> (a -> AppM c) -> AppM c

bracket_ :: AppM a -> AppM b -> AppM c -> AppM c

finally :: AppM a -> AppM b -> AppM a

MonadReader UTxO AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

ask :: AppM UTxO Source #

local :: (UTxO -> UTxO) -> AppM a -> AppM a Source #

reader :: (UTxO -> a) -> AppM a Source #

MonadState UTxO AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

get :: AppM UTxO Source #

put :: UTxO -> AppM () Source #

state :: (UTxO -> (a, UTxO)) -> AppM a Source #

RunModel Model AppM Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

perform :: Typeable a => Model -> Action Model a -> LookUp AppM -> AppM (PerformResult (Error Model) (Realized AppM a))

postcondition :: (Model, Model) -> Action Model a -> LookUp AppM -> Realized AppM a -> PostconditionM AppM Bool

postconditionOnFailure :: (Model, Model) -> Action Model a -> LookUp AppM -> Either (Error Model) (Realized AppM a) -> PostconditionM AppM Bool

monitoring :: (Model, Model) -> Action Model a -> LookUp AppM -> Either (Error Model) (Realized AppM a) -> Property -> Property

monitoringFailure :: Model -> Action Model a -> LookUp AppM -> Error Model -> Property -> Property

type Realized AppM a Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

type Realized AppM a = a

performTx :: Show err => Either err Tx -> AppM TxResult Source #

Perform a transaction by evaluating and observing it. This updates the UTxO in the AppM if a transaction is valid and produces a TxResult that can be used to assert expected success / failure.

Fixtures and glue code

allActors :: [Actor] Source #

List of all model actors corresponding to the fixtures used.

generateUTxOFromModelSnapshot :: ModelSnapshot -> (UTxO, UTxO) Source #

A "random" UTxO distribution for a given ModelSnapshot.

realWorldModelUTxO :: ModelUTxO -> UTxO Source #

Map a ModelUTxO to a real-world UTxO.

signedSnapshot :: ModelSnapshot -> (Snapshot Tx, MultiSignature (Snapshot Tx)) Source #

A correctly signed snapshot. Given a snapshot number a snapshot signed by all participants (alice, bob and carol) with some UTxO contained is produced.

confirmedSnapshot :: ModelSnapshot -> ConfirmedSnapshot Tx Source #

A confirmed snapshot (either initial or later confirmed), based onTxTra signedSnapshot.

openHeadUTxO :: UTxO Source #

UTxO of the open head on-chain. NOTE: This uses fixtures for headId, parties, and cperiod.

newDecrementTx :: Actor -> ConfirmedSnapshot Tx -> AppM (Either DecrementTxError Tx) Source #

Creates a decrement transaction using given utxo and given snapshot.

newCloseTx :: Actor -> SnapshotVersion -> ConfirmedSnapshot Tx -> AppM (Either CloseTxError Tx) Source #

Creates a transaction that closes openHeadUTxO with given the snapshot. NOTE: This uses fixtures for headId, parties (alice, bob, carol), contestation period and also claims to close at time 0 resulting in a contestation deadline of 0 + cperiod.

newContestTx :: Actor -> SnapshotVersion -> ConfirmedSnapshot Tx -> AppM (Either ContestTxError Tx) Source #

Creates a contest transaction using given utxo and contesting with given snapshot. NOTE: This uses fixtures for headId, contestation period and also claims to contest at time 0.

newFanoutTx :: Actor -> ModelUTxO -> ModelUTxO -> AppM (Either FanoutTxError Tx) Source #

Creates a fanout transaction using given utxo. NOTE: This uses fixtures for seedTxIn and contestation period. Consequently, the lower bound used is precisely at the maximum deadline slot as if everyone contested.

alicePVk :: VerificationKey PaymentKey Source #

Cardano payment keys for alice, bob, and carol.

bobPVk :: VerificationKey PaymentKey Source #

Cardano payment keys for alice, bob, and carol.

carolPVk :: VerificationKey PaymentKey Source #

Cardano payment keys for alice, bob, and carol.

actorChainContext :: Actor -> ChainContext Source #

Fixture for the chain context of a model Actor on testNetworkId. Uses a generated ScriptRegistry.

testScriptRegistry :: ScriptRegistry Source #

Helpers

runPostconditionM' :: Monad m => PostconditionM' m () -> PostconditionM m Bool Source #

Run a short-cutting variant of PostconditionM which produces True if it reaches the end, or False if fail is used.

newtype PostconditionM' m a Source #

Constructors

PostconditionM' (ExceptT (Maybe String) (PostconditionM m) a) 

Instances

Instances details
Monad m => MonadFail (PostconditionM' m) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Monad m => Alternative (PostconditionM' m) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Monad m => Applicative (PostconditionM' m) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Functor m => Functor (PostconditionM' m) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

Methods

fmap :: (a -> b) -> PostconditionM' m a -> PostconditionM' m b Source #

(<$) :: a -> PostconditionM' m b -> PostconditionM' m a Source #

Monad m => Monad (PostconditionM' m) Source # 
Instance details

Defined in Hydra.Chain.Direct.TxTraceSpec

fulfilled :: Monad m => PostconditionM' m () Source #

Short-cut a postcondition monad like fail, but in a successful way. This is useful to not have unrelated counterexample' outputs.

counterexample' :: Monad m => String -> PostconditionM' m () Source #

Add given message in case the postcondition fails.

expectValid :: Monad m => TxResult -> (HeadObservation -> PostconditionM' m a) -> PostconditionM' m a Source #

Assertion helper to check whether a TxResult was valid and the expected HeadObservation could be made. To be used in postcondition.

expectInvalid :: Monad m => TxResult -> PostconditionM' m () Source #

Assertion helper to check whether a TxResult was invalid.

orSometimes :: a -> Gen a -> Gen a Source #

Generate sometimes a value with given generator, bur more often just use the given value.