Skip to content

Commit abb4874

Browse files
jbertholdgithub-actions
andauthored
3119 output unexplored leaf count when failing (#3177)
* 3119 Output count of unexplored branches when a proof fails When a proof fails on one branch (or more, when using `--max-counterexamples`), the prover indicates with a warning if any other branches existed that were left unexplored. * Materialize Nix expressions * shut up hlint (log entries should be lazy) * fix a strictness + formatter error * add log entry to registry * test case for unexplored branch count Co-authored-by: github-actions <github-actions@github.com>
1 parent acdda75 commit abb4874

File tree

9 files changed

+104
-20
lines changed

9 files changed

+104
-20
lines changed

.hlint.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -157,6 +157,7 @@
157157
within:
158158
- GlobalMain
159159
- Kore.Log.InfoExecDepth
160+
- Kore.Log.WarnUnexploredBranches
160161

161162
- ignore: {name: "Redundant compare", within: [Kore.Syntax.Id]}
162163

kore/app/exec/Main.hs

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,9 @@ import Kore.Log.WarnBoundedModelChecker (
7575
import Kore.Log.WarnIfLowProductivity (
7676
warnIfLowProductivity,
7777
)
78+
import Kore.Log.WarnUnexploredBranches (
79+
warnUnexploredBranches,
80+
)
7881
import Kore.ModelChecker.Bounded qualified as Bounded (
7982
CheckResult (..),
8083
)
@@ -784,25 +787,25 @@ koreProve LocalOptions{execOptions, simplifierx} proveOptions = do
784787
specModule
785788
maybeAlreadyProvenModule
786789

787-
let ProveClaimsResult{stuckClaims, provenClaims} = proveResult
790+
let ProveClaimsResult{stuckClaims, provenClaims, unexplored} = proveResult
788791
let (exitCode, final) =
789792
case foldFirst stuckClaims of
790793
Nothing -> success -- stuckClaims is empty
791794
Just claim ->
792795
stuckPatterns
793796
& OrPattern.toTermLike (getClaimPatternSort $ claimPattern claim)
794797
& failure
795-
where
796-
stuckPatterns =
797-
OrPattern.fromPatterns (MultiAnd.map getStuckConfig stuckClaims)
798-
getStuckConfig =
799-
getRewritingPattern . getConfiguration . getStuckClaim
800-
claimPattern claim =
801-
claim
802-
& getStuckClaim
803-
& Lens.view lensClaimPattern
798+
where
799+
stuckPatterns =
800+
OrPattern.fromPatterns (MultiAnd.map getStuckConfig stuckClaims)
801+
getStuckConfig =
802+
getRewritingPattern . getConfiguration . getStuckClaim
803+
claimPattern = Lens.view lensClaimPattern . getStuckClaim
804+
804805
lift $ for_ saveProofs $ saveProven specModule provenClaims
805806
lift $ renderResult execOptions (unparse final)
807+
when (unexplored /= 0) $
808+
warnUnexploredBranches unexplored
806809
return (kFileLocations definition, exitCode)
807810
where
808811
failure pat = (ExitFailure 1, pat)

kore/kore.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -394,6 +394,7 @@ library
394394
Kore.Log.WarnStuckClaimState
395395
Kore.Log.WarnSymbolSMTRepresentation
396396
Kore.Log.WarnTrivialClaim
397+
Kore.Log.WarnUnexploredBranches
397398
Kore.Log.WarnUnsimplified
398399
Kore.ModelChecker.Bounded
399400
Kore.ModelChecker.Simplification

kore/src/Kore/Log/Registry.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,6 +145,9 @@ import Kore.Log.WarnSymbolSMTRepresentation (
145145
import Kore.Log.WarnTrivialClaim (
146146
WarnTrivialClaim,
147147
)
148+
import Kore.Log.WarnUnexploredBranches (
149+
WarnUnexploredBranches,
150+
)
148151
import Kore.Log.WarnUnsimplified (
149152
WarnUnsimplifiedCondition,
150153
WarnUnsimplifiedPredicate,
@@ -213,6 +216,7 @@ entryHelpDocsErr, entryHelpDocsNoErr :: [Pretty.Doc ()]
213216
, mk $ Proxy @WarnClaimRHSIsBottom
214217
, mk $ Proxy @WarnIfLowProductivity
215218
, mk $ Proxy @WarnTrivialClaim
219+
, mk $ Proxy @WarnUnexploredBranches
216220
, mk $ Proxy @DebugRetrySolverQuery
217221
, mk $ Proxy @DebugUnifyBottom
218222
, mk $ Proxy @DebugEvaluateCondition
Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
{-# LANGUAGE NoStrict #-}
2+
{-# LANGUAGE NoStrictData #-}
3+
4+
{- |
5+
Copyright : (c) Runtime Verification, 2019-2022
6+
License : BSD-3-Clause
7+
-}
8+
module Kore.Log.WarnUnexploredBranches (
9+
WarnUnexploredBranches (..),
10+
warnUnexploredBranches,
11+
) where
12+
13+
import Log
14+
import Numeric.Natural
15+
import Prelude.Kore
16+
import Pretty (
17+
Pretty,
18+
)
19+
import Pretty qualified
20+
21+
{- | @WarnUnexploredBranches@ is emitted when a proof gets stuck. It
22+
indicates how many other branches in the proof were left unexplored
23+
(and may also be failing if explored).
24+
-}
25+
data WarnUnexploredBranches
26+
= WarnUnexploredBranches Natural
27+
deriving stock (Show)
28+
29+
instance Pretty WarnUnexploredBranches where
30+
pretty (WarnUnexploredBranches count) =
31+
Pretty.pretty count
32+
Pretty.<+> "branches were still unexplored when the action failed."
33+
34+
instance Entry WarnUnexploredBranches where
35+
entrySeverity _ = Warning
36+
oneLineDoc (WarnUnexploredBranches count) =
37+
Pretty.pretty count
38+
Pretty.<+> "branches were still unexplored when the action failed."
39+
helpDoc _ =
40+
"indicate whether and how many unexplored branches existed when failing."
41+
42+
warnUnexploredBranches :: MonadLog log => Natural -> log ()
43+
warnUnexploredBranches = logEntry . WarnUnexploredBranches

kore/src/Kore/Reachability/Prove.hs

Lines changed: 16 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -152,10 +152,11 @@ lhsClaimStateTransformer sort =
152152

153153
{- | @Verifer a@ is a 'Simplifier'-based action which returns an @a@.
154154
155-
The action may throw an exception if the proof fails; the exception is a
156-
@'MultiAnd'@ of unprovable configuration.
155+
The action may throw an exception if the proof fails; the exception is
156+
a @'MultiAnd'@ of unprovable configuration and a count of unexplored
157+
branches.
157158
-}
158-
type VerifierT m = ExceptT StuckClaims m
159+
type VerifierT m = ExceptT (StuckClaims, Natural) m
159160

160161
newtype AllClaims claim = AllClaims {getAllClaims :: [claim]}
161162
newtype Axioms claim = Axioms {getAxioms :: [Rule claim]}
@@ -183,6 +184,8 @@ data ProveClaimsResult = ProveClaimsResult
183184
stuckClaims :: !StuckClaims
184185
, -- | The conjunction of all claims which were proven.
185186
provenClaims :: !ProvenClaims
187+
, -- | A count of non-final states that were not explored further
188+
unexplored :: Natural
186189
}
187190

188191
proveClaims ::
@@ -224,10 +227,12 @@ proveClaims
224227
unproven
225228
& runExceptT
226229
& flip runStateT (MultiAnd.make stillProven)
230+
let (stuckClaims, unexplored) = fromLeft (MultiAnd.top, 0) result
227231
pure
228232
ProveClaimsResult
229-
{ stuckClaims = fromLeft MultiAnd.top result
233+
{ stuckClaims
230234
, provenClaims
235+
, unexplored
231236
}
232237
where
233238
unproven :: ToProve SomeClaim
@@ -307,7 +312,7 @@ proveClaim ::
307312
AllClaims SomeClaim ->
308313
Axioms SomeClaim ->
309314
(SomeClaim, Limit Natural) ->
310-
Simplifier (Either StuckClaims ())
315+
Simplifier (Either (StuckClaims, Natural) ())
311316
proveClaim
312317
maybeMinDepth
313318
stuckCheck
@@ -335,18 +340,19 @@ proveClaim
335340
limitedStrategyList
336341
(ProofDepth 0, startGoal)
337342

338-
let returnUnprovenClaims =
343+
let returnUnprovenClaims n =
339344
pure
340345
. Left
346+
. (,fromIntegral n)
341347
. MultiAnd.make
342348
. map StuckClaim
343349
. mapMaybe (extractUnproven . snd)
344350

345351
case traversalResult of
346-
GraphTraversal.GotStuck _n rs ->
347-
returnUnprovenClaims rs
348-
GraphTraversal.Aborted _n rs ->
349-
returnUnprovenClaims rs
352+
GraphTraversal.GotStuck n rs ->
353+
returnUnprovenClaims n rs
354+
GraphTraversal.Aborted n rs ->
355+
returnUnprovenClaims n rs
350356
GraphTraversal.Ended results -> do
351357
let depths = map fst results
352358
maxProofDepth = sconcat (ProofDepth 0 :| depths)

kore/test/Test/Kore/Reachability/Prove.hs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -771,6 +771,30 @@ test_proveClaims =
771771
in [ mkTest "OnePath" simpleOnePathClaim
772772
, mkTest "AllPath" simpleAllPathClaim
773773
]
774+
, testGroup "warns about unexplored branch when one of several stuck claims returned" $
775+
let axioms = [simpleAxiom Mock.a (mkOr Mock.b Mock.c)]
776+
mkTest name mkSimpleClaim =
777+
testCase name $ do
778+
actual <-
779+
Test.Kore.Reachability.Prove.proveClaims
780+
Unlimited
781+
Unlimited
782+
1
783+
axioms
784+
[mkSimpleClaim Mock.a Mock.d]
785+
[]
786+
let stuck = mkSimpleClaim Mock.b Mock.d
787+
expect =
788+
ProveClaimsResult
789+
{ stuckClaims = MultiAnd.singleton (StuckClaim stuck)
790+
, provenClaims = MultiAnd.top
791+
, unexplored = 1
792+
}
793+
assertEqual "count" (unexplored expect) (unexplored actual)
794+
assertEqual "claim" (stuckClaims expect) (stuckClaims actual)
795+
in [ mkTest "OnePath" simpleOnePathClaim
796+
, mkTest "AllPath" simpleAllPathClaim
797+
]
774798
]
775799

776800
test_transitionRule :: TestTree

nix/kore-ghc8107.nix.d/kore.nix

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -312,6 +312,7 @@
312312
"Kore/Log/WarnStuckClaimState"
313313
"Kore/Log/WarnSymbolSMTRepresentation"
314314
"Kore/Log/WarnTrivialClaim"
315+
"Kore/Log/WarnUnexploredBranches"
315316
"Kore/Log/WarnUnsimplified"
316317
"Kore/ModelChecker/Bounded"
317318
"Kore/ModelChecker/Simplification"

nix/kore-ghc923.nix.d/kore.nix

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -312,6 +312,7 @@
312312
"Kore/Log/WarnStuckClaimState"
313313
"Kore/Log/WarnSymbolSMTRepresentation"
314314
"Kore/Log/WarnTrivialClaim"
315+
"Kore/Log/WarnUnexploredBranches"
315316
"Kore/Log/WarnUnsimplified"
316317
"Kore/ModelChecker/Bounded"
317318
"Kore/ModelChecker/Simplification"

0 commit comments

Comments
 (0)