Skip to content

Commit 3230905

Browse files
jbertholdgoodlyrottenapplegeo2aPetar Maksimovicgithub-actions
authored
Jb/trim booster ground truth (#4038)
When `booster` checks predicates with a given ground truth (a substitution and other predicates assumed true), this change filters the substitution and the ground truth to only contain predicates using relevant variables (from the predicates to check, and transitively from other relevant predicates). --------- Co-authored-by: Sam Balco <[email protected]> Co-authored-by: Georgy Lukyanov <[email protected]> Co-authored-by: Petar Maksimovic <[email protected]> Co-authored-by: github-actions <[email protected]> Co-authored-by: Petar Maksimović <[email protected]>
1 parent cfebf12 commit 3230905

File tree

5 files changed

+91
-15
lines changed

5 files changed

+91
-15
lines changed

booster/library/Booster/SMT/Interface.hs

Lines changed: 35 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -434,12 +434,23 @@ checkPredicates ctxt givenPs givenSubst psToCheck
434434
translated = SMT.runTranslator $ do
435435
let mkSMTEquation v t =
436436
SMT.eq <$> SMT.translateTerm (Var v) <*> SMT.translateTerm t
437-
smtSubst <-
438-
mapM (\(v, t) -> Assert "Substitution" <$> mkSMTEquation v t) $ Map.assocs givenSubst
439-
smtPs <-
440-
mapM (\(Predicate p) -> Assert (mkComment p) <$> SMT.translateTerm p) $ Set.toList givenPs
437+
substEqs <-
438+
mapM (uncurry mkSMTEquation) $ Map.assocs givenSubst
439+
440+
groundTruth <-
441+
mapM (\(Predicate p) -> (p,) <$> SMT.translateTerm p) $ Set.toList givenPs
442+
441443
toCheck <-
442444
mapM (SMT.translateTerm . coerce) $ Set.toList psToCheck
445+
446+
let interestingVars = mconcat $ map smtVars toCheck
447+
filteredGroundTruth = closureOver interestingVars $ Set.fromList $ map snd groundTruth
448+
filteredSubstEqs = closureOver interestingVars $ Set.fromList substEqs
449+
450+
let mkAssert (p, sexpr) = Assert (mkComment p) sexpr
451+
smtPs = map mkAssert $ filter ((`Set.member` filteredGroundTruth) . snd) groundTruth
452+
smtSubst = map (Assert "Substitution") $ Set.toList filteredSubstEqs
453+
443454
pure (smtSubst <> smtPs, toCheck)
444455

445456
-- Given the known truth and the expressions to check,
@@ -503,3 +514,23 @@ checkPredicates ctxt givenPs givenSubst psToCheck
503514
"Given ∧ P and Given ∧ !P interpreted as "
504515
<> pack (show (positive', negative'))
505516
pure (positive', negative')
517+
518+
-- functions for filtering ground truth and substitution equations
519+
smtVars :: SMT.SExpr -> Set SMT.SMTId
520+
smtVars (Atom smtId@(SMTId bs))
521+
| "SMT-" `BS.isPrefixOf` bs = Set.singleton smtId
522+
| otherwise = mempty
523+
smtVars (List exprs) = mconcat $ map smtVars exprs
524+
525+
-- filters given 'exprs' to only return those which use any of the
526+
-- SMT 'atoms' or from other expressions that are also returned.
527+
closureOver :: Set SMT.SMTId -> Set SMT.SExpr -> Set SMT.SExpr
528+
closureOver atoms exprs = loop mempty exprs atoms
529+
where
530+
loop :: Set SMT.SExpr -> Set SMT.SExpr -> Set SMT.SMTId -> Set SMT.SExpr
531+
loop acc exprs' currentAtoms =
532+
let (rest, addedExprs) = Set.partition (Set.null . Set.intersection currentAtoms . smtVars) exprs'
533+
newAtoms = Set.unions $ Set.map smtVars addedExprs
534+
in if Set.null addedExprs
535+
then acc
536+
else loop (acc <> addedExprs) rest newAtoms

kore/kore.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -569,6 +569,7 @@ library
569569
SMT
570570
SMT.AST
571571
SMT.SimpleSMT
572+
SMT.Utils
572573
SQL
573574
SQL.ColumnDef
574575
SQL.Key

kore/src/Kore/Rewrite/SMT/Evaluator.hs

Lines changed: 23 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,7 @@ import SMT (
9494
)
9595
import SMT qualified
9696
import SMT.SimpleSMT qualified as SimpleSMT
97+
import SMT.Utils qualified as SMT
9798

9899
{- | Attempt to evaluate the 'Predicate' argument with an optional side
99100
condition using an external SMT solver.
@@ -109,11 +110,13 @@ evalPredicate onUnknown predicate sideConditionM = case predicate of
109110
Predicate.PredicateFalse -> return $ Just False
110111
_ -> case sideConditionM of
111112
Nothing ->
112-
predicate :| []
113-
& decidePredicate onUnknown SideCondition.top
113+
decidePredicate onUnknown SideCondition.top [] predicate
114114
Just sideCondition ->
115-
predicate :| [from @_ @(Predicate _) sideCondition]
116-
& decidePredicate onUnknown sideCondition
115+
decidePredicate
116+
onUnknown
117+
sideCondition
118+
(Predicate.getMultiAndPredicate $ from @_ @(Predicate _) sideCondition)
119+
predicate
117120

118121
{- | Attempt to evaluate the 'Conditional' argument with an optional side
119122
condition using an external SMT solver.
@@ -164,9 +167,10 @@ decidePredicate ::
164167
InternalVariable variable =>
165168
OnDecidePredicateUnknown ->
166169
SideCondition variable ->
167-
NonEmpty (Predicate variable) ->
170+
[Predicate variable] ->
171+
Predicate variable ->
168172
Simplifier (Maybe Bool)
169-
decidePredicate onUnknown sideCondition predicates =
173+
decidePredicate onUnknown sideCondition sideConditionPredicates predicate =
170174
whileDebugEvaluateCondition predicates $
171175
do
172176
result <- query >>= whenUnknown retry
@@ -187,14 +191,23 @@ decidePredicate onUnknown sideCondition predicates =
187191
empty
188192
& runMaybeT
189193
where
194+
predicates = predicate :| sideConditionPredicates
195+
190196
query :: MaybeT Simplifier Result
191197
query = onErrorUnknown $ SMT.withSolver . evalTranslator $ do
192198
tools <- Simplifier.askMetadataTools
193199
Morph.hoist SMT.liftSMT $ do
194-
predicates' <-
195-
traverse
196-
(translatePredicate sideCondition tools)
197-
predicates
200+
sideConditionPredicates' <-
201+
concatMap SMT.splitAnd
202+
<$> traverse
203+
(translatePredicate sideCondition tools)
204+
sideConditionPredicates
205+
predicate' <- SMT.splitAnd <$> translatePredicate sideCondition tools predicate
206+
let predicates' = SMT.transitiveClosure (Set.fromList predicate') $ Set.fromList sideConditionPredicates'
207+
-- when (Set.fromList predicate' /= predicates') $ liftIO $ do
208+
-- putStrLn $ "predicate: " <> show (Set.fromList predicate')
209+
-- putStrLn $ "sideConditionPredicates: " <> show sideConditionPredicates'
210+
-- putStrLn $ "pruned to: " <> show predicates'
198211
traverse_ SMT.assert predicates'
199212
SMT.check >>= maybe empty return
200213

kore/src/SMT/Utils.hs

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
module SMT.Utils (module SMT.Utils) where
2+
3+
import Data.Set (Set)
4+
import Data.Set qualified as Set
5+
import Data.Text (Text, isPrefixOf, isSuffixOf)
6+
7+
import Prelude.Kore
8+
import SMT qualified
9+
10+
splitAnd :: SMT.SExpr -> [SMT.SExpr]
11+
splitAnd = \case
12+
SMT.List (SMT.Atom "and" : xs) -> concatMap splitAnd xs
13+
other -> [other]
14+
15+
varAtoms :: SMT.SExpr -> Set Text
16+
varAtoms = \case
17+
SMT.Atom a
18+
| "<" `isPrefixOf` a && ">" `isSuffixOf` a -> Set.singleton a
19+
| otherwise -> mempty
20+
SMT.List xs -> mconcat $ map varAtoms xs
21+
_ -> mempty
22+
23+
transitiveClosure :: Set SMT.SExpr -> Set SMT.SExpr -> Set SMT.SExpr
24+
transitiveClosure cl' rest' = loop (Set.unions (Set.map varAtoms cl')) cl' rest'
25+
where
26+
loop clVars cl rest =
27+
let (nonCommon, common) = Set.partition (null . Set.intersection clVars . varAtoms) rest
28+
in if null common
29+
then cl
30+
else loop (clVars <> Set.unions (Set.map varAtoms common)) (cl <> common) nonCommon

kore/test/Test/Kore/Rewrite/SMT/Evaluator.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -243,7 +243,8 @@ assertRefuted prop = do
243243
SMT.Evaluator.decidePredicate
244244
(ErrorDecidePredicateUnknown $srcLoc Nothing)
245245
SideCondition.top
246-
(prop :| [])
246+
[]
247+
prop
247248
& Test.runSimplifierSMT testEnv
248249
assertEqual "" expect actual
249250

0 commit comments

Comments
 (0)