Skip to content

Commit 7c8fbfb

Browse files
authored
Kore.Exec.prove: Return all failing results (#496)
* Kore.Exec.prove: Return all failing results Returning all failing results is very useful for debugging and exploration. Instead of this implementation, we may want to consider printing a flat list of patterns. The result is always a disjunction at the top, but because it is a list of patterns, that disjunction can quickly become very deeply nested. * Test.Kore.OnePath.Verification: Check for multiple results
1 parent a43ce1e commit 7c8fbfb

File tree

4 files changed

+85
-51
lines changed

4 files changed

+85
-51
lines changed

kore/src/Kore/Exec.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -59,12 +59,13 @@ import Kore.Step.BaseStep
5959
( StepProof )
6060
import Kore.Step.Pattern
6161
import Kore.Step.Representation.ExpandedPattern
62-
( CommonExpandedPattern, Predicated (..), toMLPattern )
62+
( CommonExpandedPattern, Predicated (..) )
6363
import qualified Kore.Step.Representation.ExpandedPattern as ExpandedPattern
6464
import qualified Kore.Step.Representation.ExpandedPattern as Predicated
6565
import qualified Kore.Step.Representation.MultiOr as MultiOr
6666
import Kore.Step.Representation.OrOfExpandedPattern
6767
( OrOfExpandedPattern )
68+
import qualified Kore.Step.Representation.OrOfExpandedPattern as OrOfExpandedPattern
6869
import Kore.Step.Search
6970
( searchGraph )
7071
import qualified Kore.Step.Search as Search
@@ -196,16 +197,16 @@ prove limit definitionModule specModule = do
196197
axioms = fmap Axiom rewriteRules
197198
claims = fmap makeClaim specAxioms
198199

199-
result <- runExceptT
200+
result <-
201+
runExceptT
200202
$ verify
201203
tools
202204
simplifier
203205
substitutionSimplifier
204206
axiomIdToSimplifier
205207
(defaultStrategy claims axioms)
206208
(map (\x -> (x,limit)) (extractUntrustedClaims claims))
207-
208-
return $ Bifunctor.first toMLPattern result
209+
return $ Bifunctor.first OrOfExpandedPattern.toStepPattern result
209210

210211
where
211212
makeClaim (attributes, rule) = Claim { rule , attributes }

kore/src/Kore/OnePath/Verification.hs

Lines changed: 23 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -16,16 +16,12 @@ module Kore.OnePath.Verification
1616
, verify
1717
) where
1818

19-
import Control.Monad.IO.Class
20-
( liftIO )
21-
import Control.Monad.Reader
22-
( ask )
23-
import Control.Monad.Trans.Except
24-
( ExceptT, throwE )
25-
import Data.Proxy
26-
( Proxy (..) )
27-
import Numeric.Natural
28-
( Natural )
19+
import qualified Control.Monad as Monad
20+
import Control.Monad.Trans.Except
21+
( ExceptT, throwE )
22+
import Data.Maybe
23+
import Numeric.Natural
24+
( Natural )
2925

3026
import qualified Control.Monad.Trans as Monad.Trans
3127
import Data.Limit
@@ -34,7 +30,7 @@ import qualified Data.Limit as Limit
3430
import Kore.AST.Common
3531
( Variable )
3632
import Kore.AST.MetaOrObject
37-
( IsMetaOrObject (..), MetaOrObject (..) )
33+
( MetaOrObject (..) )
3834
import qualified Kore.Attribute.Axiom as Attribute
3935
import Kore.IndexedModule.MetadataTools
4036
( MetadataTools )
@@ -57,13 +53,17 @@ import Kore.Step.Representation.ExpandedPattern as ExpandedPattern
5753
( fromPurePattern )
5854
import Kore.Step.Representation.ExpandedPattern as Predicated
5955
( Predicated (..) )
56+
import qualified Kore.Step.Representation.MultiOr as MultiOr
57+
import Kore.Step.Representation.OrOfExpandedPattern
58+
( CommonOrOfExpandedPattern )
6059
import Kore.Step.Simplification.Data
61-
( Environment (proveClaim), PredicateSubstitutionSimplifier,
62-
Simplifier, StepPatternSimplifier )
60+
( PredicateSubstitutionSimplifier, Simplifier,
61+
StepPatternSimplifier )
6362
import Kore.Step.StepperAttributes
6463
( StepperAttributes )
6564
import Kore.Step.Strategy
6665
( Strategy, pickFinal, runStrategy )
66+
import qualified Kore.TopBottom as TopBottom
6767

6868
{- | Wrapper for a rewrite rule that should be used as a claim.
6969
-}
@@ -113,7 +113,7 @@ verify
113113
-- ^ List of claims, together with a maximum number of verification steps
114114
-- for each.
115115
-> ExceptT
116-
(CommonExpandedPattern level)
116+
(CommonOrOfExpandedPattern level)
117117
Simplifier
118118
()
119119
verify
@@ -193,7 +193,7 @@ verifyClaim
193193
)
194194
-> (RewriteRule level Variable, Limit Natural)
195195
-> ExceptT
196-
(CommonExpandedPattern level)
196+
(CommonOrOfExpandedPattern level)
197197
Simplifier
198198
()
199199
verifyClaim
@@ -202,12 +202,8 @@ verifyClaim
202202
substitutionSimplifier
203203
axiomIdToSimplifier
204204
strategyBuilder
205-
(rule@(RewriteRule RulePattern {left, right, requires}), stepLimit)
205+
((RewriteRule RulePattern {left, right, requires}), stepLimit)
206206
= do
207-
pc <- proveClaim <$> ask
208-
liftIO' $ case isMetaOrObject (Proxy @level) of
209-
IsObject -> pc rule
210-
IsMeta -> pure ()
211207
let
212208
strategy =
213209
Limit.takeWithin
@@ -226,14 +222,10 @@ verifyClaim
226222
( startPattern, mempty )
227223
let
228224
finalNodes = pickFinal executionGraph
229-
nonBottomNodes = filter notBottom (map fst finalNodes)
230-
notBottom StrategyPattern.Bottom = False
231-
notBottom _ = True
232-
case nonBottomNodes of
233-
[] -> return ()
234-
StrategyPattern.RewritePattern p : _ -> throwE p
235-
StrategyPattern.Stuck p : _ -> throwE p
236-
StrategyPattern.Bottom : _ -> error "Unexpected bottom pattern."
237-
where
238-
liftIO' :: IO () -> ExceptT (CommonExpandedPattern level) Simplifier ()
239-
liftIO' = liftIO
225+
remainingNodes =
226+
MultiOr.make $ mapMaybe getRemainingNode (fst <$> finalNodes)
227+
where
228+
getRemainingNode (StrategyPattern.RewritePattern p) = Just p
229+
getRemainingNode (StrategyPattern.Stuck p) = Just p
230+
getRemainingNode StrategyPattern.Bottom = Nothing
231+
Monad.unless (TopBottom.isBottom remainingNodes) (throwE remainingNodes)

kore/src/Kore/Step/Representation/OrOfExpandedPattern.hs

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ module Kore.Step.Representation.OrOfExpandedPattern
1818
, isTrue
1919
, makeFromSinglePurePattern
2020
, toExpandedPattern
21+
, toStepPattern
2122
, toPredicate
2223
) where
2324

@@ -122,6 +123,26 @@ toExpandedPattern multiOr
122123
, substitution = mempty
123124
}
124125

126+
{-| Transforms an 'OrOfExpandedPattern' into a 'StepPattern'.
127+
-}
128+
toStepPattern
129+
:: ( MetaOrObject level
130+
, SortedVariable variable
131+
, Ord (variable level)
132+
, Show (variable level)
133+
, Unparse (variable level)
134+
)
135+
=> OrOfExpandedPattern level variable -> StepPattern level variable
136+
toStepPattern multiOr =
137+
case MultiOr.extractPatterns multiOr of
138+
[] -> mkBottom_
139+
[patt] -> ExpandedPattern.toMLPattern patt
140+
patt : patts ->
141+
foldl'
142+
(\x y -> mkOr x (ExpandedPattern.toMLPattern y))
143+
(ExpandedPattern.toMLPattern patt)
144+
patts
145+
125146
{-| Transforms an 'OrOfPredicate' into a 'Predicate'. -}
126147
toPredicate
127148
:: ( MetaOrObject level

kore/test/Test/Kore/OnePath/Verification.hs

Lines changed: 36 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,10 @@ import Kore.Step.Representation.ExpandedPattern
3737
import Kore.Step.Representation.ExpandedPattern as Predicated
3838
( Predicated (..) )
3939
import Kore.Step.Representation.ExpandedPattern as ExpandedPattern
40-
( CommonExpandedPattern, fromPurePattern )
40+
( fromPurePattern )
41+
import qualified Kore.Step.Representation.MultiOr as MultiOr
42+
import Kore.Step.Representation.OrOfExpandedPattern
43+
( CommonOrOfExpandedPattern )
4144
import Kore.Step.Simplification.Data
4245
( evalSimplifier )
4346
import qualified Kore.Step.Simplification.Simplifier as Simplifier
@@ -63,7 +66,7 @@ test_onePathVerification =
6366
[simpleAxiom Mock.a Mock.b]
6467
[simpleClaim Mock.a Mock.b]
6568
assertEqualWithExplanation ""
66-
(Left $ ExpandedPattern.fromPurePattern Mock.a)
69+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.a])
6770
actual
6871
, testCase "Runs one step" $ do
6972
-- Axiom: a => b
@@ -80,7 +83,21 @@ test_onePathVerification =
8083
[simpleAxiom Mock.a Mock.b]
8184
[simpleClaim Mock.a Mock.b]
8285
assertEqualWithExplanation ""
83-
(Left $ ExpandedPattern.fromPurePattern Mock.b)
86+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.b])
87+
actual
88+
, testCase "Returns multiple results" $ do
89+
-- Axiom: a => b or c
90+
-- Claim: a => d
91+
-- Expected: error [b, c]
92+
actual <- runVerification
93+
metadataTools
94+
(Limit 1)
95+
[simpleAxiom Mock.a (mkOr Mock.b Mock.c)]
96+
[simpleClaim Mock.a Mock.d]
97+
assertEqualWithExplanation ""
98+
(Left . MultiOr.make $
99+
ExpandedPattern.fromPurePattern <$> [Mock.b, Mock.c]
100+
)
84101
actual
85102
, testCase "Verifies one claim" $ do
86103
-- Axiom: a => b
@@ -105,7 +122,7 @@ test_onePathVerification =
105122
, simpleClaim Mock.a Mock.b
106123
]
107124
assertEqualWithExplanation ""
108-
(Left $ ExpandedPattern.fromPurePattern Mock.a)
125+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.a])
109126
actual
110127
, testCase "Verifies one claim multiple steps" $ do
111128
-- Axiom: a => b
@@ -171,12 +188,15 @@ test_onePathVerification =
171188
]
172189
[simpleClaim (Mock.functionalConstr10 (mkVar Mock.x)) Mock.b]
173190
assertEqualWithExplanation ""
174-
(Left Predicated
175-
{ term = Mock.functionalConstr11 (mkVar Mock.x)
176-
, predicate =
177-
makeNotPredicate (makeEqualsPredicate (mkVar Mock.x) Mock.a)
178-
, substitution = mempty
179-
}
191+
(Left $ MultiOr.make
192+
[ Predicated
193+
{ term = Mock.functionalConstr11 (mkVar Mock.x)
194+
, predicate =
195+
makeNotPredicate
196+
(makeEqualsPredicate (mkVar Mock.x) Mock.a)
197+
, substitution = mempty
198+
}
199+
]
180200
)
181201
actual
182202
, testCase "Verifies two claims" $ do
@@ -217,7 +237,7 @@ test_onePathVerification =
217237
, simpleClaim Mock.d Mock.e
218238
]
219239
assertEqualWithExplanation ""
220-
(Left $ ExpandedPattern.fromPurePattern Mock.c)
240+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.c])
221241
actual
222242
, testCase "fails second of two claims" $ do
223243
-- Axiom: a => b
@@ -237,7 +257,7 @@ test_onePathVerification =
237257
, simpleClaim Mock.d Mock.c
238258
]
239259
assertEqualWithExplanation ""
240-
(Left $ ExpandedPattern.fromPurePattern Mock.e)
260+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.e])
241261
actual
242262
, testCase "second proves first but fails" $ do
243263
-- Axiom: a => b
@@ -255,7 +275,7 @@ test_onePathVerification =
255275
, simpleClaim Mock.b Mock.c
256276
]
257277
assertEqualWithExplanation ""
258-
(Left $ ExpandedPattern.fromPurePattern Mock.b)
278+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.b])
259279
actual
260280
, testCase "first proves second but fails" $ do
261281
-- Axiom: a => b
@@ -273,7 +293,7 @@ test_onePathVerification =
273293
, simpleClaim Mock.a Mock.d
274294
]
275295
assertEqualWithExplanation ""
276-
(Left $ ExpandedPattern.fromPurePattern Mock.b)
296+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.b])
277297
actual
278298
, testCase "trusted second proves first" $ do
279299
-- Axiom: a => b
@@ -332,7 +352,7 @@ test_onePathVerification =
332352
, simpleClaim Mock.b Mock.e
333353
]
334354
assertEqualWithExplanation ""
335-
(Left $ ExpandedPattern.fromPurePattern Mock.e)
355+
(Left $ MultiOr.make [ExpandedPattern.fromPurePattern Mock.e])
336356
actual
337357
]
338358
where
@@ -390,7 +410,7 @@ runVerification
390410
-> Limit Natural
391411
-> [OnePath.Axiom level]
392412
-> [OnePath.Claim level]
393-
-> IO (Either (CommonExpandedPattern level) ())
413+
-> IO (Either (CommonOrOfExpandedPattern level) ())
394414
runVerification
395415
metadataTools
396416
stepLimit

0 commit comments

Comments
 (0)