-
Notifications
You must be signed in to change notification settings - Fork 12
Description
Smallest reproduction I could build:
module Specs.ConvergenceSpec where
import Control.Monad (guard)
import Data.Either qualified as Either
import Data.Type.Rec (RecF)
import Language.Spectacle
import Test.Hspec (Spec, hspec, it, shouldSatisfy)
main :: IO ()
main = hspec spec
initialStepsLeft :: Word
initialStepsLeft = 4
spec :: Spec
spec = do
it "model checks specification with stepNegative and stepPositive actions" $ do
result <-
modelcheck
( specification $
ConF #stepNegative (takeStep (pure pred)) $
ConF #stepPositive (takeStep (pure succ)) NilF
)
result `shouldSatisfy` Either.isRight
it "model checks specification with a single takeStep action that can go negative or positive" $ do
result <-
modelcheck
( specification $
ConF #takeStep (takeStep (oneOf [pred, succ])) NilF
)
result `shouldSatisfy` Either.isRight
specification ::
RecF (ActionType '["stepsLeft" # Word, "position" # Int]) acts ->
Specification
'["stepsLeft" # Word, "position" # Int]
acts
'["staysAtZero" # 'Stays]
specification specNext =
Specification
{ specInit =
ConF #stepsLeft (pure initialStepsLeft) $
ConF #position (pure 0) NilF
, specNext = specNext
, specProp =
ConF #staysAtZero atZero NilF
}
takeStep ::
Action '["stepsLeft" # Word, "position" # Int] (Int -> Int) ->
ActionType '["stepsLeft" # Word, "position" # Int] 'WeakFair
takeStep possibleSteps = ActionWF do
stepsLeft <- plain #stepsLeft
guard (stepsLeft > 0)
position <- plain #position
delta <- possibleSteps
let newPosition = delta position
guard (abs newPosition < fromIntegral stepsLeft) -- never go so far that we can't come back
#position .= pure newPosition
#stepsLeft .= pure (pred stepsLeft)
pure True
atZero :: TemporalType '["stepsLeft" # Word, "position" # Int] 'Stays
atZero = PropFG $ ((0 :: Int) ==) <$> plain #position
The spec models a behaviour where we start at 0, there are a finite number of steps to be taken, and we never take a step away from 0 if it would take us to a distance that is too far to go back. We should be able to move around, but eventually, we should end up stuck at position == 0 (with either 1 or 0 steps left, depending on whether the initial number of steps is odd or even).
In the first test case, we have two possible actions: stepNegative
tries to decrease the position, stepPositive tries to increase the position. In the second test case, we have a single action takeStep
that uses oneOf
to decide whether to decrease or increase the position.
I would expect both cases to be equivalent,. However, the first test case passes, while the second fails.
For some reason, I'm only able to reproduce if initialStepsLeft
is >= 4.