Skip to content
This repository was archived by the owner on Aug 1, 2023. It is now read-only.

Commit 132f96c

Browse files
ksaricCodiePP
authored andcommitted
[GH-96] T1.2.1 QuickCheck state machine tests, added example. (#166)
* [GH-96] T1.2.1 QuickCheck state machine tests, added example. * [GH-96] Fixed Nix deps.
1 parent 6ba4a88 commit 132f96c

File tree

7 files changed

+199
-9
lines changed

7 files changed

+199
-9
lines changed

Makefile

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,4 +22,8 @@ test-ghci: ## Run repl on test suites
2222
test-ghcid: ## Run ghcid on test suites
2323
@ghcid --command "stack ghci $(PROJECT_NAME):lib $(PROJECT_NAME):test:$(PROJECT_NAME)-test --ghci-options=-fobject-code"
2424

25-
.PHONY: stylish-haskell ghcid ghcid-test run-test test-ghci test-ghcid help
25+
test-ghcid-nix: ## Run ghcid on test suites with Nix
26+
#NUM_PROC = $(nproc --all) # Either try to fetch the real num of cores or default to 4
27+
@ghcid --command="stack ghci --test --main-is cardano-shell:test:cardano-shell-test --nix -j12"
28+
29+
.PHONY: stylish-haskell ghcid ghcid-test run-test test-ghci test-ghcid help

cardano-shell.cabal

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -175,7 +175,7 @@ executable cardano-launcher
175175
-Wincomplete-record-updates
176176
-Wincomplete-uni-patterns
177177
-Wredundant-constraints
178-
-Wpartial-fields
178+
-Wpartial-fields
179179

180180
test-suite cardano-shell-test
181181
type: exitcode-stdio-1.0
@@ -186,6 +186,7 @@ test-suite cardano-shell-test
186186
if !os(windows)
187187
other-modules:
188188
NodeIPCSpec
189+
NodeIPCSMSpec
189190

190191
hs-source-dirs:
191192
test
@@ -199,6 +200,10 @@ test-suite cardano-shell-test
199200
, safe-exceptions
200201
-- quickcheck
201202
, QuickCheck
203+
, quickcheck-state-machine >= 0.6
204+
-- required because of QSM
205+
, tree-diff
206+
, stm
202207
, hspec
203208
, hspec-contrib
204209
, concurrency
@@ -208,7 +213,7 @@ test-suite cardano-shell-test
208213
default-extensions: NoImplicitPrelude
209214
OverloadedStrings
210215

211-
ghc-options: -Wall
216+
ghc-options:
212217
-Werror
213218
-Wcompat
214219
-Wincomplete-record-updates

nix/.stack.nix/cardano-shell.nix

Lines changed: 4 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

nix/.stack.nix/default.nix

Lines changed: 2 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

stack.yaml

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,8 @@ packages:
4040
# using the same syntax as the packages field.
4141
# (e.g., acme-missiles-0.3)
4242
extra-deps:
43+
- quickcheck-state-machine-0.6.0 # Used a specific dependency, new release.
44+
4345
- git: https://github.com/input-output-hk/cardano-prelude
4446
commit: 2256fd727c5f92e6218afdcf8cddf6e01c4a9dcd
4547
subdirs:
@@ -60,11 +62,8 @@ extra-deps:
6062
- .
6163

6264
- katip-0.7.0.0@sha256:4b30d0643e18d01a3fd264d3d75921b49b2f464336a52fa46fa049107ebbfe04
63-
6465
- time-units-1.0.0@sha256:27cf54091c4a0ca73d504fc11d5c31ab4041d17404fe3499945e2055697746c1
65-
6666
- ekg-0.4.0.15@sha256:f52d7c00654d72d2ab988255f30adba95a52484ac310bab9c136c64732e69f4b
67-
6867
- ekg-json-0.1.0.6@sha256:4ff2e9cac213a5868ae8b4a7c72a16a9a76fac14d944ae819b3d838a9725569b
6968

7069
- ekg-prometheus-adapter-0.1.0.4

test/NodeIPCSMSpec.hs

Lines changed: 176 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,176 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE DeriveAnyClass #-}
3+
{-# LANGUAGE DeriveGeneric #-}
4+
{-# LANGUAGE FlexibleInstances #-}
5+
{-# LANGUAGE KindSignatures #-}
6+
{-# LANGUAGE LambdaCase #-}
7+
{-# LANGUAGE PolyKinds #-}
8+
{-# LANGUAGE StandaloneDeriving #-}
9+
10+
module NodeIPCSMSpec
11+
( mkEnv
12+
, prop_echoOK
13+
, prop_echoParallelOK
14+
) where
15+
16+
import Cardano.Prelude
17+
18+
import Control.Concurrent.STM (TVar, newTVarIO, readTVar, writeTVar)
19+
20+
import Data.Kind (Type)
21+
import Data.TreeDiff (ToExpr (..))
22+
23+
import GHC.Generics (Generic, Generic1)
24+
import Prelude
25+
import Test.QuickCheck (Gen, Property, arbitrary, oneof, (===))
26+
import Test.QuickCheck.Monadic (monadicIO)
27+
28+
import Test.StateMachine
29+
import Test.StateMachine.Types
30+
import qualified Test.StateMachine.Types.Rank2 as Rank2
31+
32+
------------------------------------------------------------------------
33+
34+
-- | Echo API.
35+
36+
data Env = Env
37+
{ _buf :: TVar (Maybe String) }
38+
39+
-- | Create a new environment.
40+
mkEnv :: IO Env
41+
mkEnv = Env <$> newTVarIO Nothing
42+
43+
-- | Input a string. Returns 'True' iff the buffer was empty and the given
44+
-- string was added to it.
45+
input :: Env -> String -> IO Bool
46+
input (Env mBuf) str = atomically $ do
47+
res <- readTVar mBuf
48+
case res of
49+
Nothing -> writeTVar mBuf (Just str) >> return True
50+
Just _ -> return False
51+
52+
-- | Output the buffer contents.
53+
output :: Env -> IO (Maybe String)
54+
output (Env mBuf) = atomically $ do
55+
res <- readTVar mBuf
56+
writeTVar mBuf Nothing
57+
return res
58+
59+
------------------------------------------------------------------------
60+
61+
-- | Spec for echo.
62+
63+
prop_echoOK :: Property
64+
prop_echoOK = forAllCommands smUnused Nothing $ \cmds -> monadicIO $ do
65+
env <- liftIO $ mkEnv
66+
let echoSM' = echoSM env
67+
(hist, _, res) <- runCommands echoSM' cmds
68+
prettyCommands echoSM' hist (res === Ok)
69+
70+
prop_echoParallelOK :: Bool -> Property
71+
prop_echoParallelOK problem = forAllParallelCommands smUnused $ \cmds -> monadicIO $ do
72+
env <- liftIO $ mkEnv
73+
let echoSM' = echoSM env
74+
let n | problem = 2
75+
| otherwise = 1
76+
prettyParallelCommands cmds =<< runParallelCommandsNTimes n echoSM' cmds
77+
78+
smUnused :: StateMachine Model Action IO Response
79+
smUnused = echoSM $ error "used env during command generation"
80+
81+
echoSM :: Env -> StateMachine Model Action IO Response
82+
echoSM env = StateMachine
83+
{ initModel = Empty
84+
-- ^ At the beginning of time nothing was received.
85+
, transition = mTransitions
86+
, precondition = mPreconditions
87+
, postcondition = mPostconditions
88+
, generator = mGenerator
89+
, invariant = Nothing
90+
, shrinker = mShrinker
91+
, semantics = mSemantics
92+
, mock = mMock
93+
, distribution = Nothing
94+
}
95+
where
96+
mTransitions :: Model r -> Action r -> Response r -> Model r
97+
mTransitions Empty (In str) _ = Buf str
98+
mTransitions (Buf _) Echo _ = Empty
99+
mTransitions Empty Echo _ = Empty
100+
-- TODO: qcsm will match the case below. However we don't expect this to happen!
101+
mTransitions (Buf str) (In _) _ = Buf str -- Dummy response
102+
-- error "This shouldn't happen: input transition with full buffer"
103+
104+
-- | There are no preconditions for this model.
105+
mPreconditions :: Model Symbolic -> Action Symbolic -> Logic
106+
mPreconditions _ _ = Top
107+
108+
-- | Post conditions for the system.
109+
mPostconditions :: Model Concrete -> Action Concrete -> Response Concrete -> Logic
110+
mPostconditions Empty (In _) InAck = Top
111+
mPostconditions (Buf _) (In _) ErrFull = Top
112+
mPostconditions _ (In _) _ = Bot
113+
mPostconditions Empty Echo ErrEmpty = Top
114+
mPostconditions Empty Echo _ = Bot
115+
mPostconditions (Buf str) Echo (Out out) = str .== out
116+
mPostconditions (Buf _) Echo _ = Bot
117+
118+
-- | Generator for symbolic actions.
119+
mGenerator :: Model Symbolic -> Maybe (Gen (Action Symbolic))
120+
mGenerator _ = Just $ oneof
121+
[ In <$> arbitrary
122+
, return Echo
123+
]
124+
125+
-- | Trivial shrinker.
126+
mShrinker :: Model Symbolic -> Action Symbolic -> [Action Symbolic]
127+
mShrinker _ _ = []
128+
129+
-- | Here we'd do the dispatch to the actual SUT.
130+
mSemantics :: Action Concrete -> IO (Response Concrete)
131+
mSemantics (In str) = do
132+
success <- input env str
133+
return $ if success
134+
then InAck
135+
else ErrFull
136+
mSemantics Echo = maybe ErrEmpty Out <$> output env
137+
138+
-- | What is the mock for?
139+
mMock :: Model Symbolic -> Action Symbolic -> GenSym (Response Symbolic)
140+
mMock Empty (In _) = return InAck
141+
mMock (Buf _) (In _) = return ErrFull
142+
mMock Empty Echo = return ErrEmpty
143+
mMock (Buf str) Echo = return (Out str)
144+
145+
deriving instance ToExpr (Model Concrete)
146+
147+
-- | The model contains the last string that was communicated in an input
148+
-- action.
149+
data Model (r :: Type -> Type)
150+
= -- | The model hasn't been initialized.
151+
Empty
152+
| -- | Last input string (a buffer with size one).
153+
Buf String
154+
deriving (Eq, Show, Generic)
155+
156+
-- | Actions supported by the system.
157+
data Action (r :: Type -> Type)
158+
= -- | Input a string, which should be echoed later.
159+
In String
160+
-- | Request a string output.
161+
| Echo
162+
deriving (Show, Generic1, Rank2.Foldable, Rank2.Traversable, Rank2.Functor, CommandNames)
163+
164+
-- | The system gives a single type of output response, containing a string
165+
-- with the input previously received.
166+
data Response (r :: Type -> Type)
167+
= -- | Input acknowledgment.
168+
InAck
169+
-- | The previous action wasn't an input, so there is no input to echo.
170+
-- This is: the buffer is empty.
171+
| ErrEmpty
172+
-- | There is already a string in the buffer.
173+
| ErrFull
174+
-- | Output string.
175+
| Out String
176+
deriving (Show, Generic1, Rank2.Foldable, Rank2.Traversable, Rank2.Functor)

test/Spec.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ import Cardano.Prelude
88
import Control.Concurrent.Classy (MonadConc)
99
import Control.Exception.Safe (throwM)
1010
import Test.DejaFu (abortsNever, deadlocksNever, exceptionsNever)
11-
import Test.Hspec (Spec, describe, hspec)
11+
import Test.Hspec (Spec, describe, hspec, it)
1212
import Test.Hspec.Contrib.HUnit (fromHUnitTest)
1313
import Test.HUnit.DejaFu (testDejafu)
1414
import Test.QuickCheck (Gen, arbitraryASCIIChar, choose, frequency,
@@ -20,13 +20,15 @@ import Cardano.Shell.Types (CardanoFeature (..))
2020

2121
import DhallConfigSpec (dhallConfigSpec, mkConfigSpec)
2222
import NodeIPCSpec (nodeIPCSpec)
23+
import NodeIPCSMSpec
2324

2425
-- | Entry point for tests.
2526
main :: IO ()
2627
main = hspec $ do
2728
describe "App should have no concurrency issues" validConcurrencySpec
2829
describe "Dhall configurations" dhallConfigSpec
2930
describe "Cardano configurations" mkConfigSpec
31+
describe "NodeIPC state machine example" $ it "check the example works" prop_echoOK
3032
describe "NodeIPC" nodeIPCSpec
3133

3234
-- | A valid concurrency specification.

0 commit comments

Comments
 (0)