Skip to content

Commit 3fb0874

Browse files
Create a Kore.Reachability context (#2141)
* mv Kore.Strategies.Goal Kore.Reachability.Claim * Kore.Reachability.Claim: Remove unprovenNodes and proven * Import Kore.Reachability.Claim as Claim * Rename ReachabilityRule to ReachabilityClaim * Kore.Repl.Data: Remove Claim type synonym * Rename Goal to Claim * Move data family Rule into Claim class * Rename ProofState to ClaimState The data type does not represent the state of the entire proof, but only the state of a single claim. * ClaimState: Rename constructors * Extract Kore.Reachability.Prim from Kore.Reachability.ClaimState * mv Kore.Strategies.Verification Kore.Reachability.Prove * Kore.Reachability.Prove: rename verify to proveClaims * mv Test.Kore.Strategies Test.Kore.Reachability * Kore.Reachability: AllPathClaim, OnePathClaim, SomeClaim * Rename ReachabilityClaim to SomeClaim There are three types which represent reachability logic claims (AllPathClaim, OnePathClaim, and SomeClaim) so it did not make sense to call out SomeClaim as _the_ ReachabilityClaim. The prefix Some- matches the typical naming convention of collecting multiple subtypes in a sum type. * HLint cleanup * kore-exec: fix build * Test.Kore.Reachability: move all prove tests to Prove.hs, remove duplicates * Test.Kore.Reachability.Prove: clean-up exports * Move Test.Kore.Strategies.OnePath.Step * Update kore/src/Kore/Reachability/ClaimState.hs Co-authored-by: ana-pantilie <[email protected]> * Kore.Reachability.ClaimState: Alignment * OnePathClaim: Remove obsolete comment * SentenceVerifier: Use extractClaim * Add Test.Expect.expectJust * QualifiedAxiomPattern: Remove reachability claims * Remove Kore.Reachability.SomeClaim.toSentence * MockAllPath: Rename Goal to MockClaim * MockAllPath: HLint Co-authored-by: ana-pantilie <[email protected]> Co-authored-by: ana-pantilie <[email protected]>
1 parent 6ab0ba3 commit 3fb0874

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

45 files changed

+2892
-3253
lines changed

kore/app/exec/Main.hs

Lines changed: 12 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -132,12 +132,13 @@ import Kore.Parser
132132
( ParsedPattern
133133
, parseKorePattern
134134
)
135+
import Kore.Reachability
136+
( ProofStuck (..)
137+
, SomeClaim
138+
)
139+
import qualified Kore.Reachability.Claim as Claim
135140
import Kore.Rewriting.RewritingVariable
136141
import Kore.Step
137-
import Kore.Step.ClaimPattern
138-
( ReachabilityRule
139-
, toSentence
140-
)
141142
import Kore.Step.RulePattern
142143
( RewriteRule
143144
)
@@ -149,10 +150,6 @@ import Kore.Step.SMT.Lemma
149150
import Kore.Step.Strategy
150151
( GraphSearchOrder (..)
151152
)
152-
import qualified Kore.Strategies.Goal as Goal
153-
import Kore.Strategies.Verification
154-
( Stuck (..)
155-
)
156153
import Kore.Syntax.Definition
157154
( Definition (Definition)
158155
, Module (Module)
@@ -611,9 +608,9 @@ mainWithOptions execOptions = do
611608
Nothing -> errorException someException
612609
throwM someException
613610

614-
handleWithConfiguration :: Goal.WithConfiguration -> Main ExitCode
611+
handleWithConfiguration :: Claim.WithConfiguration -> Main ExitCode
615612
handleWithConfiguration
616-
(Goal.WithConfiguration lastConfiguration someException)
613+
(Claim.WithConfiguration lastConfiguration someException)
617614
= do
618615
liftIO $ renderResult
619616
execOptions
@@ -697,7 +694,7 @@ koreProve execOptions proveOptions = do
697694
maybeAlreadyProvenModule
698695

699696
(exitCode, final) <- case proveResult of
700-
Left Stuck { stuckPatterns, provenClaims } -> do
697+
Left ProofStuck { stuckPatterns, provenClaims } -> do
701698
maybe
702699
(return ())
703700
(lift . saveProven specModule provenClaims)
@@ -733,7 +730,7 @@ koreProve execOptions proveOptions = do
733730

734731
saveProven
735732
:: VerifiedModule StepperAttributes
736-
-> [ReachabilityRule]
733+
-> [SomeClaim]
737734
-> FilePath
738735
-> IO ()
739736
saveProven specModule provenClaims outputFile =
@@ -753,13 +750,15 @@ koreProve execOptions proveOptions = do
753750
isNotAxiomOrClaim (SentenceSortSentence _) = True
754751
isNotAxiomOrClaim (SentenceHookSentence _) = True
755752

753+
provenClaimSentences = map (from @SomeClaim @(Sentence _)) provenClaims
756754
provenModule =
757755
Module
758756
{ moduleName = savedProofsModuleName
759757
, moduleSentences =
760-
specModuleDefinitions <> fmap toSentence provenClaims
758+
specModuleDefinitions <> provenClaimSentences
761759
, moduleAttributes = def
762760
}
761+
763762
provenDefinition = Definition
764763
{ definitionAttributes = def
765764
, definitionModules = [provenModule]

kore/src/Kore/ASTVerifier/SentenceVerifier.hs

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -79,18 +79,17 @@ import qualified Kore.Internal.Symbol as Internal.Symbol
7979
import Kore.Internal.TermLike.TermLike
8080
( freeVariables
8181
)
82+
import Kore.Reachability
83+
( SomeClaim
84+
, extractClaim
85+
, lensClaimPattern
86+
)
8287
import Kore.Sort
8388
import Kore.Step.ClaimPattern
84-
( AllPathRule (..)
85-
, ClaimPattern
86-
, OnePathRule (..)
89+
( ClaimPattern
8790
, freeVariablesLeft
8891
, freeVariablesRight
8992
)
90-
import Kore.Step.Rule
91-
( QualifiedAxiomPattern (..)
92-
, fromSentenceAxiom
93-
)
9493
import Kore.Syntax.Definition
9594
import Kore.Syntax.Variable
9695
import qualified Kore.Verified as Verified
@@ -406,12 +405,11 @@ verifyClaimSentence sentence =
406405
(field @"indexedModuleClaims")
407406
((attrs, verified) :)
408407
rejectClaim attrs verified =
409-
case fromSentenceAxiom (attrs, verified) of
410-
Right (OnePathClaimPattern (OnePathRule claimPattern))
411-
| rejectClaimPattern claimPattern -> True
412-
Right (AllPathClaimPattern (AllPathRule claimPattern))
413-
| rejectClaimPattern claimPattern -> True
414-
_ -> False
408+
do
409+
someClaim <- extractClaim @SomeClaim (attrs, SentenceClaim verified)
410+
let claimPattern = Lens.view lensClaimPattern someClaim
411+
pure (rejectClaimPattern claimPattern)
412+
& fromMaybe False
415413
rejectClaimPattern :: ClaimPattern -> Bool
416414
rejectClaimPattern claimPattern =
417415
not $ Set.isSubsetOf freeRightVars freeLeftVars

kore/src/Kore/Exec.hs

Lines changed: 34 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -105,14 +105,23 @@ import Kore.Log.KoreLogOptions
105105
)
106106
import Kore.Log.WarnTrivialClaim
107107
import qualified Kore.ModelChecker.Bounded as Bounded
108+
import Kore.Reachability
109+
( AllClaims (AllClaims)
110+
, AlreadyProven (AlreadyProven)
111+
, Axioms (Axioms)
112+
, ProofStuck (..)
113+
, Rule (ReachabilityRewriteRule)
114+
, SomeClaim (..)
115+
, ToProve (ToProve)
116+
, extractClaims
117+
, isTrusted
118+
, lensClaimPattern
119+
, proveClaims
120+
)
108121
import qualified Kore.Repl as Repl
109122
import qualified Kore.Repl.Data as Repl.Data
110123
import Kore.Rewriting.RewritingVariable
111124
import Kore.Step
112-
import Kore.Step.ClaimPattern
113-
( ReachabilityRule (..)
114-
, lensClaimPattern
115-
)
116125
import Kore.Step.Rule
117126
( extractImplicationClaims
118127
, extractRewriteAxioms
@@ -156,15 +165,6 @@ import qualified Kore.Step.Strategy as Strategy
156165
import Kore.Step.Transition
157166
( runTransitionT
158167
)
159-
import qualified Kore.Strategies.Goal as Goal
160-
import Kore.Strategies.Verification
161-
( AllClaims (AllClaims)
162-
, AlreadyProven (AlreadyProven)
163-
, Axioms (Axioms)
164-
, Stuck (..)
165-
, ToProve (ToProve)
166-
, verify
167-
)
168168
import Kore.Syntax.Module
169169
( ModuleName
170170
)
@@ -386,7 +386,7 @@ prove
386386
-- ^ The spec module
387387
-> Maybe (VerifiedModule StepperAttributes)
388388
-- ^ The module containing the claims that were proven in a previous run.
389-
-> smt (Either Stuck ())
389+
-> smt (Either ProofStuck ())
390390
prove
391391
searchOrder
392392
breadthLimit
@@ -402,7 +402,7 @@ prove
402402
specModule
403403
trustedModule
404404
let InitializedProver { axioms, claims, alreadyProven } = initialized
405-
verify
405+
proveClaims
406406
breadthLimit
407407
searchOrder
408408
(AllClaims claims)
@@ -415,8 +415,8 @@ prove
415415
)
416416
& runExceptT
417417
where
418-
extractUntrustedClaims' :: [ReachabilityRule] -> [ReachabilityRule]
419-
extractUntrustedClaims' = filter (not . Goal.isTrusted)
418+
extractUntrustedClaims' :: [SomeClaim] -> [SomeClaim]
419+
extractUntrustedClaims' = filter (not . isTrusted)
420420

421421
-- | Initialize and run the repl with the main and spec modules. This will loop
422422
-- the repl until the user exits.
@@ -650,11 +650,11 @@ makeImplicationRule
650650
makeImplicationRule (attributes, ImplicationRule rulePattern) =
651651
ImplicationRule rulePattern { attributes }
652652

653-
simplifyReachabilityRule
653+
simplifySomeClaim
654654
:: MonadSimplify simplifier
655-
=> ReachabilityRule
656-
-> simplifier ReachabilityRule
657-
simplifyReachabilityRule rule = do
655+
=> SomeClaim
656+
-> simplifier SomeClaim
657+
simplifySomeClaim rule = do
658658
let claim = Lens.view lensClaimPattern rule
659659
claim' <- Rule.simplifyClaimPattern claim
660660
return $ Lens.set lensClaimPattern claim' rule
@@ -684,9 +684,9 @@ initialize verifiedModule = do
684684

685685
data InitializedProver =
686686
InitializedProver
687-
{ axioms :: ![Goal.Rule ReachabilityRule]
688-
, claims :: ![ReachabilityRule]
689-
, alreadyProven :: ![ReachabilityRule]
687+
{ axioms :: ![Rule SomeClaim]
688+
, claims :: ![SomeClaim]
689+
, alreadyProven :: ![SomeClaim]
690690
}
691691

692692
data MaybeChanged a = Changed !a | Unchanged !a
@@ -707,39 +707,35 @@ initializeProver definitionModule specModule maybeTrustedModule = do
707707
initialized <- initialize definitionModule
708708
tools <- Simplifier.askMetadataTools
709709
let Initialized { rewriteRules } = initialized
710-
changedSpecClaims :: [MaybeChanged ReachabilityRule]
711-
changedSpecClaims =
712-
expandClaim tools <$> Goal.extractClaims specModule
713-
simplifyToList
714-
:: ReachabilityRule
715-
-> simplifier [ReachabilityRule]
710+
changedSpecClaims :: [MaybeChanged SomeClaim]
711+
changedSpecClaims = expandClaim tools <$> extractClaims specModule
712+
simplifyToList :: SomeClaim -> simplifier [SomeClaim]
716713
simplifyToList rule = do
717714
simplified <- simplifyRuleLhs rule
718715
let result = MultiAnd.extractPatterns simplified
719716
when (null result) $ warnTrivialClaimRemoved rule
720717
return result
721718

722-
trustedClaims :: [ReachabilityRule]
723-
trustedClaims =
724-
fmap Goal.extractClaims maybeTrustedModule & fromMaybe []
719+
trustedClaims :: [SomeClaim]
720+
trustedClaims = fmap extractClaims maybeTrustedModule & fromMaybe []
725721

726722
mapM_ logChangedClaim changedSpecClaims
727723

728-
let specClaims :: [ReachabilityRule]
724+
let specClaims :: [SomeClaim]
729725
specClaims = map fromMaybeChanged changedSpecClaims
730726
-- This assertion should come before simplifying the claims,
731727
-- since simplification should remove all trivial claims.
732728
assertSomeClaims specClaims
733729
simplifiedSpecClaims <- mapM simplifyToList specClaims
734-
claims <- traverse simplifyReachabilityRule (concat simplifiedSpecClaims)
730+
claims <- traverse simplifySomeClaim (concat simplifiedSpecClaims)
735731
let axioms = coerce <$> rewriteRules
736732
alreadyProven = trustedClaims
737733
pure InitializedProver { axioms, claims, alreadyProven }
738734
where
739735
expandClaim
740736
:: SmtMetadataTools attributes
741-
-> ReachabilityRule
742-
-> MaybeChanged ReachabilityRule
737+
-> SomeClaim
738+
-> MaybeChanged SomeClaim
743739
expandClaim tools claim =
744740
if claim /= expanded
745741
then Changed expanded
@@ -748,7 +744,7 @@ initializeProver definitionModule specModule maybeTrustedModule = do
748744
expanded = expandSingleConstructors tools claim
749745

750746
logChangedClaim
751-
:: MaybeChanged ReachabilityRule
747+
:: MaybeChanged SomeClaim
752748
-> simplifier ()
753749
logChangedClaim (Changed claim) =
754750
Log.logInfo ("Claim variables were expanded:\n" <> unparseToText claim)

kore/src/Kore/Log/DebugProofState.hs renamed to kore/src/Kore/Log/DebugClaimState.hs

Lines changed: 15 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -3,36 +3,38 @@ Copyright : (c) Runtime Verification, 2020
33
License : NCSA
44
-}
55

6-
module Kore.Log.DebugProofState
7-
( DebugProofState (..)
6+
module Kore.Log.DebugClaimState
7+
( DebugClaimState (..)
88
) where
99

1010
import Prelude.Kore
1111

12-
import Kore.Step.ClaimPattern
13-
( ReachabilityRule (..)
12+
import Kore.Reachability.ClaimState
13+
( ClaimState (..)
1414
)
15-
import Kore.Strategies.ProofState
15+
import Kore.Reachability.Prim
1616
( Prim (..)
17-
, ProofState (..)
17+
)
18+
import Kore.Reachability.SomeClaim
19+
( SomeClaim (..)
1820
)
1921
import Log
2022
import Pretty
2123
( Pretty (..)
2224
)
2325
import qualified Pretty
2426

25-
data DebugProofState =
26-
DebugProofState
27-
{ proofState :: ProofState ReachabilityRule
27+
data DebugClaimState =
28+
DebugClaimState
29+
{ proofState :: ClaimState SomeClaim
2830
, transition :: Prim
29-
, result :: Maybe (ProofState ReachabilityRule)
31+
, result :: Maybe (ClaimState SomeClaim)
3032
}
3133
deriving (Show)
3234

33-
instance Pretty DebugProofState where
35+
instance Pretty DebugClaimState where
3436
pretty
35-
DebugProofState
37+
DebugClaimState
3638
{ proofState
3739
, transition
3840
, result
@@ -47,6 +49,6 @@ instance Pretty DebugProofState where
4749
, Pretty.indent 4 (maybe "Terminal state." pretty result)
4850
]
4951

50-
instance Entry DebugProofState where
52+
instance Entry DebugClaimState where
5153
entrySeverity _ = Debug
5254
helpDoc _ = "log proof state"

kore/src/Kore/Log/DebugProven.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -9,16 +9,16 @@ module Kore.Log.DebugProven
99

1010
import Prelude.Kore
1111

12-
import Kore.Step.ClaimPattern
13-
( ReachabilityRule (..)
12+
import Kore.Reachability.SomeClaim
13+
( SomeClaim (..)
1414
)
1515
import Log
1616
import Pretty
1717
( Pretty (..)
1818
)
1919
import qualified Pretty
2020

21-
newtype DebugProven = DebugProven { claim :: ReachabilityRule }
21+
newtype DebugProven = DebugProven { claim :: SomeClaim }
2222
deriving (Show)
2323

2424
instance Pretty DebugProven where

kore/src/Kore/Log/InfoReachability.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,9 +10,7 @@ module Kore.Log.InfoReachability
1010

1111
import Prelude.Kore
1212

13-
import Kore.Strategies.ProofState
14-
( Prim (..)
15-
)
13+
import Kore.Reachability.Prim
1614
import Log
1715
import Pretty
1816
( Doc

0 commit comments

Comments
 (0)