Model-Based Testing with QuickCheck

Arnaud Bailly - @dr_c0d3

2024-03-15

Agenda

  • Why?
  • Property-Based Testing
  • quickcheck-dynamic: Practice
  • quickcheck-dynamic: Theory
  • Conclusion

Why?

The Quest for Better Software

Going full circle

Automata Testing Test-Driven Development Property-Based Testing Model-Based Testing

Engineering vs. Science

Dijkstra on Testing

My Goals for this Talk

  • Share my experience with Model-Based testing to…
  • … spark interest in the use of this family of tools and …
  • … trigger contributions to improve quickcheck-dynamic

What can you expect?

  • An overview of an interesting new tool
  • “From the trenches” report on the usefulness of model-based testing
  • Tips & tricks on how and what to model

Property-Based Testing

What is Property-Based Testing?

  • Example-based testing Property-Based Testing
  • Generalise examples to express properties of the SUT

Classical examples

elements_are_sorted :: [a] -> Property
elements_are_sorted list =
  let sorted = sort list
  in undefined  --- TBD

Classical examples

roundtrip_encoding_decoding :: a -> Property
roundtrip_encoding_decoding a =
  let encoded = encode a
      decoded = decode encoded
  in decoded === Just a

QuickCheck Core Features

  • Generate some number of arbitrary values…
  • … when property fails, shrink the failing input …
  • … to provide smallest counterexample upon failure

Additional Key Features

Stateful QuickCheck

  • Monadic version of QC
  • Running properties against stateful (IO) programs
Testing Monadic code with QuickCheck

Stateful QuickCheck

  • Define a Domain-Specific Language of inputs to the SUT
  • Provide a Model of the expected behaviour
  • Run the Model and the SUT in parallel with an arbitrary sequence of actions
  • Compare the results

Example: A Basic Repository Interface

Real-life example drawn from personal tool that needs to read/write events in a database.

Define a GADT of “interesting” Actions to run

-- | Relevant commands issued to the underlying DB
data Action a where
  WriteEvent :: Event -> Action ()
  ReadEvents :: Pagination -> Action EventsQueryResult
  ...
  NewUser :: UserProfile -> Action ()
  SwitchUser :: Text -> Action ()

Interpret actions against a Model

interpret :: (Monad m, Eq a, Show a) => Action a -> StateT Model m (Maybe a)
interpret (WriteEvent f) = do
  modify $ \m@Model {events} -> m {events = events |> EventView {index = fromIntegral (Seq.length events + 1), event = f}}
  pure $ Just ()
interpret (ReadEvents (Page pageNum size)) = do
  es <- getEvents
  ...

Generate (meaningful) sequence of Actions:

generateActions :: Model -> Gen Actions
generateActions model =
  Actions <$>
    (arbitrary >>=
       generateAction startTime model . getPositive)

Run interpreter and SUT in parallel and check conformance:

canReadFlowsAndTracesWritten ::
  (DB db, HasCallStack) =>
  FilePath -> (forall x. db x -> IO x) -> Property
canReadFlowsAndTracesWritten dbFile nt =
  forAllShrink (generateActions start) shrinkActions $
    \(Actions actions) -> monadicIO $ do
      res <- run $ nt $
        initLogStorage >> evalStateT (validateActions actions) start
      forM_ res monitorErrors
      assert $ all isNothing res

quickcheck-dynamic: Practice

The need for a better tool

  • Ad-hoc model-based testing has limitations
  • Quviq people are experts in these techniques and they were building a tool for IOG
  • I was involved in a complex project that would benefit from a comprehensive testing strategy

Hydra - Overview

  • A Layer-2 network for UTxO blockchains based on State channels
  • Complex on-chain protocol advancing a state-machine through transactions
  • Off-chain leader-based distributed consensus
  • More details at https://hydra.family
High-level Hydra Protocol
Hydra Deployment

Hydra - Model

Hydra Test Architecture

Hydra - Model

Hydra - Properties

Original research paper defines several key properties

Conflict-free liveness

Properties are (manually) expressed as Dynamic Logic formulas

conflictFreeLiveness = do
  anyActions_
  getModelStateDL >>= \case
    Open{} -> do
      payment <- forAllNonVariableQ (nonConflictingTx st)
      tx <- action $ Model.NewTx payment
      eventually (ObserveConfirmedTx tx)
Hydra Property Execution

Peras

  • Fast finality protocol for Cardano
  • Early work integrating research, formal methods, engineering…
  • Use quickcheck-dynamic to produce Executable Specification from Formal Specification

The slogan is:

Agda Proofs are Quickcheck Tests

Development Workflow
Testing Architecture

Testing Common Prefix property

 describe "IOSim Network" $
   prop "Chain progress" $
     prop_common_prefix iOSimNetwork

 describe "Netsim Network" $
    prop "Chain progress" $
      withMaxSuccess 20 $
        prop_common_prefix netsimNetwork

Testing Common Prefix property

chainCommonPrefix = do
  anyActions_
  getModelStateDL >>= \Network{nodeIds} -> do
    anyAction
    chains <- forM nodeIds (action . ObserveBestChain)
    void $ action $ ChainsHaveCommonPrefix chains

quickcheck-dynamic: Theory

What is it?

  • A library for Property-Based testing of stateful systems
  • Developed by Quviq while working at Input Output on Cardano
  • Open-sourced in 2022

Principles

  • Model programs as labelled transition systems
  • Express properties as Dynamic Logic formulas
  • Generate sequence of actions respecting the property
  • Run sequence of actions against SUT and find bugs!

Model - Basic steps

Specify possibles actions and initialState

instance StateModel KV where
  data Action KV a where
     Put :: String -> Int -> MySystem ()
     Get :: String -> MySystem (Maybe Int)

  initialState :: KV
  initialState = mempty

Model - Basic steps

Generate actions according to the current state

instance StateModel KV where
  initialState = ...
  arbitraryAction env state =
    oneof [ genWrite
          , genRead
          ]
    ...

Model - Basic steps

Define nextState transition

instance StateModel KV where
  initialState = ...
  arbitraryAction = ...
  nextState state (Put k v) variable =
     insert state k v
  nextState state (Get k) variable =
     state

Implementation

Relate the specification to an actual (monadic) implementation

instance RunModel KV StoreM where
  perform state (Put k v) env = do { putStore k v }
  perform state (Get k) env = do { getStore k }

Implementation

Specify postconditions that should hold after each Action

instance RunModel KV StoreM where
  perform state (Put k v) env =  ...
  postcondition (before, after) (Put k) env v = pure True
  postcondition (before, after) (Get k) env v =
    pure $ v == lookup env k

Dynamic Logic

  • A Modal logic to define properties over traces of a system
  • Exposed as both an expression and monadic DSL
  • Provide combinators to relate results of actions to predicates over the state of the SUT
Dynamic Logic book

Dynamic Logic - Syntax

Modality: [a]p

  • After a p

    After action a, p holds

  • AfterAny p

    After any action a, p holds

Constants: 𝟘,

  • Stop

    When execution Stops, expression is true

  • Empty

    When no execution is possible, expression is false

Alternatives: [a ∪ b]p, [a ∩ b]p

  • Alt Demonic f g

    After a or b p must hold

  • Alt Angelic f g

    p must hold After either a or b

Dynamic Logic - Monadic Syntax

Provide a more convenient syntax

newtype DL s a = DL { ... }
  deriving (Functor, Applicative, Alternative, Monad)

action :: Action s a -> DL s (Var a)
anyAction :: DL s ()
anyActions :: Int -> DL s ()
getModelStateDL :: DL s s
...

Combinator to Generate arbitrary values within expression

class  Quantifiable q  where
  type Quantifies q

  quantify :: q -> Quantification (Quantifies q)

forAllQ :: Quantifiable q => q -> DL s (Quantifies q)

Examples

From Thread Registry example

Can register an unbound thread under a new name

canRegister = do
  anyActions_
  name <- pickFreshName
  tid <- pickAlive
  unregisterNameAndTid name tid
  action $ Register name tid

Cannot register an already registered thread under a new name

canRegisterNoUnregister = do
  anyActions_
  name <- pickFreshName
  tid <- pickAlive
  action $ Register name tid
  pure ()

Running Properties

Tie Dynamic Logic expression and Actions execution into a Property

forAllDL ::
     (DL.DynLogicModel s, Testable a)
  => DL s ()
  -> (Actions s -> a)
  -> Property

Running Properties

Tie StateModel and RunModel, interpreting Actions against the SUT

runActions
  :: forall state m e
   . ( StateModel state
     , RunModel state m
     )
  => Actions state
  -> PropertyM m (Annotated state, Env m)

Shrinking

Sequence of actions that fail are shrank while respecting DL expression

  • Shorten anyActions_ traces
  • Shrink action and anyAction data according to model’s shrinkAction
  • Shrink Quantifiable values generated
  • precondition filters invalid sequence of actions

Anatomy of a test run

Anatomy of a test run

Anatomy of a test run

Anatomy of a test run

Anatomy of a test run

Anatomy of a test run

Anatomy of a test run

Testing for safety

  • We often want to test that nothing bad can happen, eg. safety properties
  • We can express that in the model through Polarity of Actions:
    • A Positive action is valid w.r.t to the state and is expected to succeed when run
    • A Negative action is invalid in current state and is expected to fail

Testing for safety

Testing for safety

Testing for safety

Testing for safety

Testing for safety

Conclusion

Reflecting on practical use

  • Tests execution does not catch much bugs beyond some regressions
  • But test failures in development often pinpoints blind spots and misunderstandings
  • Main benefit is to help us clarify and formalise our thoughts on the protocols
  • It requires non-negligible investment to build and maintain

Tips & Tricks

  • Model does not have to be unique
    • Tailor models to specific problems
  • Model is code hence can be buggy
    • Test-drive your generators, shrinkers, doubles…
  • It’s easy to delude yourself
    • See it fail!
  • StateModel works with symbolic values
    • Model expectations in postcondition

Tips & Tricks (contd.)

  • Detailed modeling leads to complex code
    • Abstract the uninteresting bits away
  • Acting on and observing internal state is tricky
    • Make the SUT testable and observable
  • IO Dependencies make tests slow and brittle
    • Abstract dependencies behind simulatable interfaces
  • Triggering environment failures
    • Simulate runtime environment for fault injections

Tips & Tricks (end)

Model-Based Testing work hand-in-hand with Test-Driven Development

What’s next?

Development on quickcheck-dynamic is fairly active, with plans for:

  • Parallel testing of properties for “race conditions” detection (à la quickcheck-state-machine)
  • Improved shrinking
  • More documentation, examples, use cases…

Takeaway

A plan is useless, planning is everything

Gal. von Moltke

Takeaway

A model is useless, modeling is everything

quickcheck-dynamic

Questions?