Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
30 commits
Select commit Hold shift + click to select a range
ac29f80
mv Kore.Strategies.Goal Kore.Reachability.Claim
ttuegel Sep 4, 2020
a104d56
Kore.Reachability.Claim: Remove unprovenNodes and proven
ttuegel Sep 11, 2020
3d4cb84
Import Kore.Reachability.Claim as Claim
ttuegel Sep 11, 2020
751a9b1
Rename ReachabilityRule to ReachabilityClaim
ttuegel Sep 11, 2020
70b7b75
Kore.Repl.Data: Remove Claim type synonym
ttuegel Sep 11, 2020
b93f35a
Rename Goal to Claim
ttuegel Sep 11, 2020
a2b9cc7
Move data family Rule into Claim class
ttuegel Sep 11, 2020
777e623
Rename ProofState to ClaimState
ttuegel Sep 11, 2020
90c58fe
ClaimState: Rename constructors
ttuegel Sep 11, 2020
3eeaf96
Extract Kore.Reachability.Prim from Kore.Reachability.ClaimState
ttuegel Sep 12, 2020
704642a
mv Kore.Strategies.Verification Kore.Reachability.Prove
ttuegel Sep 12, 2020
340c22a
Kore.Reachability.Prove: rename verify to proveClaims
ttuegel Sep 13, 2020
575a0a2
mv Test.Kore.Strategies Test.Kore.Reachability
ttuegel Sep 13, 2020
560472f
Kore.Reachability: AllPathClaim, OnePathClaim, SomeClaim
ttuegel Sep 14, 2020
58911fd
Rename ReachabilityClaim to SomeClaim
ttuegel Sep 14, 2020
b650e75
HLint cleanup
ttuegel Sep 14, 2020
56a8c7d
kore-exec: fix build
ttuegel Sep 14, 2020
83a800f
Test.Kore.Reachability: move all prove tests to Prove.hs, remove dupl…
ana-pantilie Sep 15, 2020
8c9bcd7
Test.Kore.Reachability.Prove: clean-up exports
ana-pantilie Sep 15, 2020
914864f
Move Test.Kore.Strategies.OnePath.Step
ana-pantilie Sep 15, 2020
6275c2a
Update kore/src/Kore/Reachability/ClaimState.hs
ttuegel Sep 15, 2020
f1347b1
Kore.Reachability.ClaimState: Alignment
ttuegel Sep 15, 2020
436b104
OnePathClaim: Remove obsolete comment
ttuegel Sep 15, 2020
129f09d
SentenceVerifier: Use extractClaim
ttuegel Sep 15, 2020
e909e55
Add Test.Expect.expectJust
ttuegel Sep 17, 2020
f3614f2
QualifiedAxiomPattern: Remove reachability claims
ttuegel Sep 16, 2020
3b33fd0
Remove Kore.Reachability.SomeClaim.toSentence
ttuegel Sep 17, 2020
0793667
Merge branch 'master' into refactor--reachability
ttuegel Sep 17, 2020
8fde47f
MockAllPath: Rename Goal to MockClaim
ttuegel Sep 17, 2020
32faf89
MockAllPath: HLint
ttuegel Sep 18, 2020
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
25 changes: 12 additions & 13 deletions kore/app/exec/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -132,12 +132,13 @@ import Kore.Parser
( ParsedPattern
, parseKorePattern
)
import Kore.Reachability
( ProofStuck (..)
, SomeClaim
)
import qualified Kore.Reachability.Claim as Claim
import Kore.Rewriting.RewritingVariable
import Kore.Step
import Kore.Step.ClaimPattern
( ReachabilityRule
, toSentence
)
import Kore.Step.RulePattern
( RewriteRule
)
Expand All @@ -149,10 +150,6 @@ import Kore.Step.SMT.Lemma
import Kore.Step.Strategy
( GraphSearchOrder (..)
)
import qualified Kore.Strategies.Goal as Goal
import Kore.Strategies.Verification
( Stuck (..)
)
import Kore.Syntax.Definition
( Definition (Definition)
, Module (Module)
Expand Down Expand Up @@ -611,9 +608,9 @@ mainWithOptions execOptions = do
Nothing -> errorException someException
throwM someException

handleWithConfiguration :: Goal.WithConfiguration -> Main ExitCode
handleWithConfiguration :: Claim.WithConfiguration -> Main ExitCode
handleWithConfiguration
(Goal.WithConfiguration lastConfiguration someException)
(Claim.WithConfiguration lastConfiguration someException)
= do
liftIO $ renderResult
execOptions
Expand Down Expand Up @@ -697,7 +694,7 @@ koreProve execOptions proveOptions = do
maybeAlreadyProvenModule

(exitCode, final) <- case proveResult of
Left Stuck { stuckPatterns, provenClaims } -> do
Left ProofStuck { stuckPatterns, provenClaims } -> do
maybe
(return ())
(lift . saveProven specModule provenClaims)
Expand Down Expand Up @@ -733,7 +730,7 @@ koreProve execOptions proveOptions = do

saveProven
:: VerifiedModule StepperAttributes
-> [ReachabilityRule]
-> [SomeClaim]
-> FilePath
-> IO ()
saveProven specModule provenClaims outputFile =
Expand All @@ -753,13 +750,15 @@ koreProve execOptions proveOptions = do
isNotAxiomOrClaim (SentenceSortSentence _) = True
isNotAxiomOrClaim (SentenceHookSentence _) = True

provenClaimSentences = map (from @SomeClaim @(Sentence _)) provenClaims
provenModule =
Module
{ moduleName = savedProofsModuleName
, moduleSentences =
specModuleDefinitions <> fmap toSentence provenClaims
specModuleDefinitions <> provenClaimSentences
, moduleAttributes = def
}

provenDefinition = Definition
{ definitionAttributes = def
, definitionModules = [provenModule]
Expand Down
24 changes: 11 additions & 13 deletions kore/src/Kore/ASTVerifier/SentenceVerifier.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,18 +79,17 @@ import qualified Kore.Internal.Symbol as Internal.Symbol
import Kore.Internal.TermLike.TermLike
( freeVariables
)
import Kore.Reachability
( SomeClaim
, extractClaim
, lensClaimPattern
)
import Kore.Sort
import Kore.Step.ClaimPattern
( AllPathRule (..)
, ClaimPattern
, OnePathRule (..)
( ClaimPattern
, freeVariablesLeft
, freeVariablesRight
)
import Kore.Step.Rule
( QualifiedAxiomPattern (..)
, fromSentenceAxiom
)
import Kore.Syntax.Definition
import Kore.Syntax.Variable
import qualified Kore.Verified as Verified
Expand Down Expand Up @@ -406,12 +405,11 @@ verifyClaimSentence sentence =
(field @"indexedModuleClaims")
((attrs, verified) :)
rejectClaim attrs verified =
case fromSentenceAxiom (attrs, verified) of
Right (OnePathClaimPattern (OnePathRule claimPattern))
| rejectClaimPattern claimPattern -> True
Right (AllPathClaimPattern (AllPathRule claimPattern))
| rejectClaimPattern claimPattern -> True
_ -> False
do
someClaim <- extractClaim @SomeClaim (attrs, SentenceClaim verified)
let claimPattern = Lens.view lensClaimPattern someClaim
pure (rejectClaimPattern claimPattern)
& fromMaybe False
rejectClaimPattern :: ClaimPattern -> Bool
rejectClaimPattern claimPattern =
not $ Set.isSubsetOf freeRightVars freeLeftVars
Expand Down
72 changes: 34 additions & 38 deletions kore/src/Kore/Exec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -105,14 +105,23 @@ import Kore.Log.KoreLogOptions
)
import Kore.Log.WarnTrivialClaim
import qualified Kore.ModelChecker.Bounded as Bounded
import Kore.Reachability
( AllClaims (AllClaims)
, AlreadyProven (AlreadyProven)
, Axioms (Axioms)
, ProofStuck (..)
, Rule (ReachabilityRewriteRule)
, SomeClaim (..)
, ToProve (ToProve)
, extractClaims
, isTrusted
, lensClaimPattern
, proveClaims
)
import qualified Kore.Repl as Repl
import qualified Kore.Repl.Data as Repl.Data
import Kore.Rewriting.RewritingVariable
import Kore.Step
import Kore.Step.ClaimPattern
( ReachabilityRule (..)
, lensClaimPattern
)
import Kore.Step.Rule
( extractImplicationClaims
, extractRewriteAxioms
Expand Down Expand Up @@ -156,15 +165,6 @@ import qualified Kore.Step.Strategy as Strategy
import Kore.Step.Transition
( runTransitionT
)
import qualified Kore.Strategies.Goal as Goal
import Kore.Strategies.Verification
( AllClaims (AllClaims)
, AlreadyProven (AlreadyProven)
, Axioms (Axioms)
, Stuck (..)
, ToProve (ToProve)
, verify
)
import Kore.Syntax.Module
( ModuleName
)
Expand Down Expand Up @@ -386,7 +386,7 @@ prove
-- ^ The spec module
-> Maybe (VerifiedModule StepperAttributes)
-- ^ The module containing the claims that were proven in a previous run.
-> smt (Either Stuck ())
-> smt (Either ProofStuck ())
prove
searchOrder
breadthLimit
Expand All @@ -402,7 +402,7 @@ prove
specModule
trustedModule
let InitializedProver { axioms, claims, alreadyProven } = initialized
verify
proveClaims
breadthLimit
searchOrder
(AllClaims claims)
Expand All @@ -415,8 +415,8 @@ prove
)
& runExceptT
where
extractUntrustedClaims' :: [ReachabilityRule] -> [ReachabilityRule]
extractUntrustedClaims' = filter (not . Goal.isTrusted)
extractUntrustedClaims' :: [SomeClaim] -> [SomeClaim]
extractUntrustedClaims' = filter (not . isTrusted)

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

simplifyReachabilityRule
simplifySomeClaim
:: MonadSimplify simplifier
=> ReachabilityRule
-> simplifier ReachabilityRule
simplifyReachabilityRule rule = do
=> SomeClaim
-> simplifier SomeClaim
simplifySomeClaim rule = do
let claim = Lens.view lensClaimPattern rule
claim' <- Rule.simplifyClaimPattern claim
return $ Lens.set lensClaimPattern claim' rule
Expand Down Expand Up @@ -684,9 +684,9 @@ initialize verifiedModule = do

data InitializedProver =
InitializedProver
{ axioms :: ![Goal.Rule ReachabilityRule]
, claims :: ![ReachabilityRule]
, alreadyProven :: ![ReachabilityRule]
{ axioms :: ![Rule SomeClaim]
, claims :: ![SomeClaim]
, alreadyProven :: ![SomeClaim]
}

data MaybeChanged a = Changed !a | Unchanged !a
Expand All @@ -707,39 +707,35 @@ initializeProver definitionModule specModule maybeTrustedModule = do
initialized <- initialize definitionModule
tools <- Simplifier.askMetadataTools
let Initialized { rewriteRules } = initialized
changedSpecClaims :: [MaybeChanged ReachabilityRule]
changedSpecClaims =
expandClaim tools <$> Goal.extractClaims specModule
simplifyToList
:: ReachabilityRule
-> simplifier [ReachabilityRule]
changedSpecClaims :: [MaybeChanged SomeClaim]
changedSpecClaims = expandClaim tools <$> extractClaims specModule
simplifyToList :: SomeClaim -> simplifier [SomeClaim]
simplifyToList rule = do
simplified <- simplifyRuleLhs rule
let result = MultiAnd.extractPatterns simplified
when (null result) $ warnTrivialClaimRemoved rule
return result

trustedClaims :: [ReachabilityRule]
trustedClaims =
fmap Goal.extractClaims maybeTrustedModule & fromMaybe []
trustedClaims :: [SomeClaim]
trustedClaims = fmap extractClaims maybeTrustedModule & fromMaybe []

mapM_ logChangedClaim changedSpecClaims

let specClaims :: [ReachabilityRule]
let specClaims :: [SomeClaim]
specClaims = map fromMaybeChanged changedSpecClaims
-- This assertion should come before simplifying the claims,
-- since simplification should remove all trivial claims.
assertSomeClaims specClaims
simplifiedSpecClaims <- mapM simplifyToList specClaims
claims <- traverse simplifyReachabilityRule (concat simplifiedSpecClaims)
claims <- traverse simplifySomeClaim (concat simplifiedSpecClaims)
let axioms = coerce <$> rewriteRules
alreadyProven = trustedClaims
pure InitializedProver { axioms, claims, alreadyProven }
where
expandClaim
:: SmtMetadataTools attributes
-> ReachabilityRule
-> MaybeChanged ReachabilityRule
-> SomeClaim
-> MaybeChanged SomeClaim
expandClaim tools claim =
if claim /= expanded
then Changed expanded
Expand All @@ -748,7 +744,7 @@ initializeProver definitionModule specModule maybeTrustedModule = do
expanded = expandSingleConstructors tools claim

logChangedClaim
:: MaybeChanged ReachabilityRule
:: MaybeChanged SomeClaim
-> simplifier ()
logChangedClaim (Changed claim) =
Log.logInfo ("Claim variables were expanded:\n" <> unparseToText claim)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,36 +3,38 @@ Copyright : (c) Runtime Verification, 2020
License : NCSA
-}

module Kore.Log.DebugProofState
( DebugProofState (..)
module Kore.Log.DebugClaimState
( DebugClaimState (..)
) where

import Prelude.Kore

import Kore.Step.ClaimPattern
( ReachabilityRule (..)
import Kore.Reachability.ClaimState
( ClaimState (..)
)
import Kore.Strategies.ProofState
import Kore.Reachability.Prim
( Prim (..)
, ProofState (..)
)
import Kore.Reachability.SomeClaim
( SomeClaim (..)
)
import Log
import Pretty
( Pretty (..)
)
import qualified Pretty

data DebugProofState =
DebugProofState
{ proofState :: ProofState ReachabilityRule
data DebugClaimState =
DebugClaimState
{ proofState :: ClaimState SomeClaim
, transition :: Prim
, result :: Maybe (ProofState ReachabilityRule)
, result :: Maybe (ClaimState SomeClaim)
}
deriving (Show)

instance Pretty DebugProofState where
instance Pretty DebugClaimState where
pretty
DebugProofState
DebugClaimState
{ proofState
, transition
, result
Expand All @@ -47,6 +49,6 @@ instance Pretty DebugProofState where
, Pretty.indent 4 (maybe "Terminal state." pretty result)
]

instance Entry DebugProofState where
instance Entry DebugClaimState where
entrySeverity _ = Debug
helpDoc _ = "log proof state"
6 changes: 3 additions & 3 deletions kore/src/Kore/Log/DebugProven.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,16 +9,16 @@ module Kore.Log.DebugProven

import Prelude.Kore

import Kore.Step.ClaimPattern
( ReachabilityRule (..)
import Kore.Reachability.SomeClaim
( SomeClaim (..)
)
import Log
import Pretty
( Pretty (..)
)
import qualified Pretty

newtype DebugProven = DebugProven { claim :: ReachabilityRule }
newtype DebugProven = DebugProven { claim :: SomeClaim }
deriving (Show)

instance Pretty DebugProven where
Expand Down
4 changes: 1 addition & 3 deletions kore/src/Kore/Log/InfoReachability.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,7 @@ module Kore.Log.InfoReachability

import Prelude.Kore

import Kore.Strategies.ProofState
( Prim (..)
)
import Kore.Reachability.Prim
import Log
import Pretty
( Doc
Expand Down
Loading