Skip to content

Commit 1739884

Browse files
ttuegelrv-jenkins
andauthored
Prove infeasible states (#1950)
* test/issue-1665 * Add InferDefined step to reachability strategy For now, this step applies only to patterns that cannot be rewritten further, to avoid getting stuck. Later, this will also be used to avoid repeated generation of the same \ceil patterns. Co-authored-by: rv-jenkins <[email protected]>
1 parent 3888160 commit 1739884

File tree

7 files changed

+112
-5
lines changed

7 files changed

+112
-5
lines changed

kore/src/Kore/Strategies/Goal.hs

Lines changed: 52 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,9 @@ import Kore.Internal.Pattern
8585
( Pattern
8686
)
8787
import qualified Kore.Internal.Pattern as Pattern
88+
import Kore.Internal.Predicate
89+
( makeCeilPredicate_
90+
)
8891
import qualified Kore.Internal.SideCondition as SideCondition
8992
import Kore.Internal.Symbol
9093
( Symbol
@@ -199,6 +202,11 @@ class Goal goal where
199202
-- checkImplication.
200203
isTriviallyValid :: goal -> Bool
201204

205+
inferDefined
206+
:: MonadSimplify m
207+
=> goal
208+
-> Strategy.TransitionT (Rule goal) m goal
209+
202210
checkImplication
203211
:: MonadSimplify m
204212
=> goal -> m (CheckImplicationResult goal)
@@ -277,8 +285,9 @@ simplifies the implementation. However, this assumption is not an essential
277285
feature of the algorithm. You should not rely on this assumption elsewhere. This
278286
decision is subject to change without notice.
279287
280-
This instance contains the default implementation for a one-path strategy. You can apply it to the
281-
first two arguments and pass the resulting function to 'Kore.Strategies.Verification.verify'.
288+
This instance contains the default implementation for a one-path strategy. You
289+
can apply it to the first two arguments and pass the resulting function to
290+
'Kore.Strategies.Verification.verify'.
282291
283292
Things to note when implementing your own:
284293
@@ -304,6 +313,8 @@ instance Goal OnePathRule where
304313

305314
isTriviallyValid = isTriviallyValid' _Unwrapped
306315

316+
inferDefined = inferDefined' _Unwrapped
317+
307318
deriveSeqOnePath
308319
:: MonadSimplify simplifier
309320
=> [Rule OnePathRule]
@@ -331,6 +342,7 @@ instance Goal AllPathRule where
331342
simplify = simplify' _Unwrapped
332343
checkImplication = checkImplication' _Unwrapped
333344
isTriviallyValid = isTriviallyValid' _Unwrapped
345+
inferDefined = inferDefined' _Unwrapped
334346
applyClaims claims = deriveSeqAllPath (map goalToRule claims)
335347

336348
applyAxioms axiomss = \goal ->
@@ -406,6 +418,15 @@ instance Goal ReachabilityRule where
406418
isTriviallyValid (AllPath goal) = isTriviallyValid goal
407419
isTriviallyValid (OnePath goal) = isTriviallyValid goal
408420

421+
inferDefined (AllPath goal) =
422+
inferDefined goal
423+
& fmap AllPath
424+
& allPathTransition
425+
inferDefined (OnePath goal) =
426+
inferDefined goal
427+
& fmap OnePath
428+
& onePathTransition
429+
409430
applyClaims claims (AllPath goal) =
410431
applyClaims (mapMaybe maybeAllPath claims) goal
411432
& fmap (fmap AllPath)
@@ -498,6 +519,13 @@ transitionRule claims axiomGroups = transitionRuleWorker
498519
Profile.timeStrategy "Goal.SimplifyRemainder"
499520
$ GoalRemainder <$> simplify goal
500521

522+
transitionRuleWorker InferDefined (GoalRemainder goal) =
523+
Profile.timeStrategy "inferDefined" $ do
524+
results <- tryTransitionT (inferDefined goal)
525+
case results of
526+
[] -> return Proven
527+
_ -> GoalRemainder <$> Transition.scatter results
528+
501529
transitionRuleWorker CheckImplication (Goal goal) =
502530
Profile.timeStrategy "Goal.CheckImplication" $ do
503531
result <- checkImplication goal
@@ -559,6 +587,7 @@ reachabilityFirstStep =
559587
, CheckGoalStuck
560588
, CheckGoalRemainder
561589
, Simplify
590+
, InferDefined
562591
, TriviallyValid
563592
, CheckImplication
564593
, ApplyAxioms
@@ -574,6 +603,7 @@ reachabilityNextStep =
574603
, CheckGoalStuck
575604
, CheckGoalRemainder
576605
, Simplify
606+
, InferDefined
577607
, TriviallyValid
578608
, CheckImplication
579609
, ApplyClaims
@@ -623,7 +653,10 @@ checkImplication' lensRulePattern goal =
623653
do
624654
removal <- removalPatterns destination configuration existentials
625655
when (isTop removal) (succeed . NotImplied $ rulePattern)
626-
let configAndRemoval = fmap (configuration <*) removal
656+
let definedConfig =
657+
Pattern.andCondition configuration
658+
$ from $ makeCeilPredicate_ (Conditional.term configuration)
659+
let configAndRemoval = fmap (definedConfig <*) removal
627660
sideCondition =
628661
Pattern.withoutTerm configuration
629662
& SideCondition.fromCondition
@@ -669,6 +702,22 @@ simplify' lensRulePattern =
669702
then pure Pattern.bottom
670703
else Foldable.asum (pure <$> configs)
671704

705+
inferDefined'
706+
:: MonadSimplify m
707+
=> Lens' goal (RulePattern VariableName)
708+
-> goal
709+
-> Strategy.TransitionT (Rule goal) m goal
710+
inferDefined' lensRulePattern =
711+
Lens.traverseOf (lensRulePattern . RulePattern.leftPattern) $ \config -> do
712+
let definedConfig =
713+
Pattern.andCondition config
714+
$ from $ makeCeilPredicate_ (Conditional.term config)
715+
configs <-
716+
simplifyTopConfiguration definedConfig
717+
>>= SMT.Evaluator.filterMultiOr
718+
& lift
719+
Foldable.asum (pure <$> configs)
720+
672721
isTriviallyValid' :: Lens' goal (RulePattern variable) -> goal -> Bool
673722
isTriviallyValid' lensRulePattern =
674723
isBottom . RulePattern.left . Lens.view lensRulePattern

kore/src/Kore/Strategies/ProofState.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,10 @@ data Prim
3838
-- ^ Mark all goals rewritten previously as new goals.
3939
| Simplify
4040
| CheckImplication
41+
-- ^ Check if the claim's implication is valid.
42+
| InferDefined
43+
-- ^ Infer that the left-hand side of the claim is defined. This is related
44+
-- to 'CheckImplication', but separated as an optimization.
4145
| TriviallyValid
4246
| ApplyClaims
4347
| ApplyAxioms
@@ -50,6 +54,7 @@ instance Pretty Prim where
5054
pretty ResetGoal = "Transition ResetGoal."
5155
pretty Simplify = "Transition Simplify."
5256
pretty CheckImplication = "Transition CheckImplication."
57+
pretty InferDefined = "infer left-hand side is defined"
5358
pretty TriviallyValid = "Transition TriviallyValid."
5459
pretty ApplyClaims = "apply claims"
5560
pretty ApplyAxioms = "apply axioms"

kore/test/Test/Kore/Strategies/AllPath/AllPath.hs

Lines changed: 22 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Test.Kore.Strategies.AllPath.AllPath
33
, test_transitionRule_CheckProven
44
, test_transitionRule_CheckGoalRem
55
, test_transitionRule_CheckImplication
6+
, test_transitionRule_InferDefined
67
, test_transitionRule_TriviallyValid
78
, test_transitionRule_ApplyClaims
89
, test_transitionRule_ApplyAxioms
@@ -226,6 +227,19 @@ test_transitionRule_ApplyAxioms =
226227
-> TestTree
227228
derives rules = equals_ (run rules $ ProofState.GoalRemainder (A, C))
228229

230+
test_transitionRule_InferDefined :: [TestTree]
231+
test_transitionRule_InferDefined =
232+
[ unmodified ProofState.Proven
233+
, unmodified (ProofState.Goal (A, B))
234+
, unmodified (ProofState.GoalStuck (A, B))
235+
, ProofState.GoalRemainder (NotDef, B) `becomes` (ProofState.Proven, mempty)
236+
]
237+
where
238+
run = runTransitionRule [] [] ProofState.InferDefined
239+
unmodified :: HasCallStack => ProofState -> TestTree
240+
unmodified state = run state `equals_` [(state, mempty)]
241+
becomes initial final = run initial `equals_` [final]
242+
229243
test_runStrategy :: [TestTree]
230244
test_runStrategy =
231245
[ [] `proves` (A, A)
@@ -240,7 +254,8 @@ test_runStrategy =
240254

241255
, [Rule (A, A)] `proves` (A, B)
242256
, [Rule (A, A)] `proves` (A, C)
243-
, [Rule (A, A)] `disproves` (A, C) $ []
257+
258+
, [Rule (A, NotDef)] `disproves` (A, C) $ []
244259

245260
, fmap Rule [(A, B), (A, C)] `proves` (A, BorC)
246261
, fmap Rule [(A, B), (A, C)] `disproves` (A, B ) $ [(C, B)]
@@ -307,7 +322,7 @@ insEdge
307322
insEdge = Strategy.insEdge
308323

309324
-- | Simple program configurations for unit testing.
310-
data K = BorC | A | B | C | D | E | F | Bot
325+
data K = BorC | A | B | C | D | E | F | NotDef | Bot
311326
deriving (Eq, GHC.Generic, Ord, Show)
312327

313328
instance SOP.Generic K
@@ -346,6 +361,7 @@ newtype instance Goal.Rule Goal =
346361
instance Goal.Goal Goal where
347362
checkImplication (src, dst)
348363
| src' == Bot = return Goal.Implied
364+
| src == NotDef = return Goal.Implied
349365
| otherwise = return $ Goal.NotImplied (src', dst)
350366
where
351367
src' = difference src dst
@@ -356,6 +372,10 @@ instance Goal.Goal Goal where
356372

357373
simplify = return
358374

375+
inferDefined goal@(src, _)
376+
| src == NotDef = empty
377+
| otherwise = pure goal
378+
359379
applyClaims claims = derivePar (map Rule claims)
360380

361381
applyAxioms axiomGroups = derivePar (concat axiomGroups)

test/issue-1665/Makefile

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
include $(CURDIR)/../include.mk

test/issue-1665/issue-1665-spec.k

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module VERIFICATION
2+
import TEST
3+
endmodule
4+
5+
module ISSUE-1665-SPEC
6+
import VERIFICATION
7+
8+
// Proving this claim requires inferring that the left-hand side of an
9+
// intermediate proof goal is defined.
10+
//
11+
rule <k> begin _ => end ?_ </k>
12+
endmodule
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
#True

test/issue-1665/test.k

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
module TEST-SYNTAX
2+
import INT
3+
4+
syntax Pgm ::= "begin" Int | "end" Int
5+
syntax Int ::= fun(Int) [function, no-evaluators]
6+
syntax Bool ::= isFun(Int) [function, functional, no-evaluators]
7+
8+
endmodule
9+
10+
module TEST
11+
import TEST-SYNTAX
12+
13+
configuration <k> $PGM:Pgm </k>
14+
15+
rule begin X => end fun(X)
16+
17+
rule [ceil-fun]: #Ceil(fun(X:Int)) => #True requires isFun(X) [anywhere, simplification]
18+
19+
endmodule

0 commit comments

Comments
 (0)