Skip to content

Commit 09a73ad

Browse files
committed
Account for incomplete rules
1 parent 858295d commit 09a73ad

File tree

2 files changed

+24
-5
lines changed

2 files changed

+24
-5
lines changed

booster/library/Booster/Pattern/Rewrite.hs

Lines changed: 23 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ import Booster.Pattern.Pretty
7070
import Booster.Pattern.Util
7171
import Booster.Prettyprinter
7272
import Booster.SMT.Interface qualified as SMT
73+
import Booster.SMT.Runner qualified as SMT
7374
import Booster.Syntax.Json.Externalise (externalisePredicate, externaliseSort, externaliseTerm)
7475
import Booster.Util (Flag (..))
7576

@@ -198,7 +199,18 @@ rewriteStep cutLabels terminalLabels pat = do
198199
RewriteStuck{} -> pure $ RewriteTrivial pat
199200
other -> pure other
200201
AppliedRules ([], _remainder) -> processGroups rest
201-
AppliedRules ([(rule, newPat, _subst)], _remainder)
202+
AppliedRules ([(rule, newPat, _subst)], remainder)
203+
| not (Set.null remainder) && not (any isFalse remainder) -> do
204+
-- a non-trivial remainder with a single applicable rule is
205+
-- an indication if semantics incompleteness: abort
206+
-- TODO refactor remainder check into a function and reuse below
207+
solver <- getSolver
208+
logMessage (show (SMT.options solver))
209+
satRes <- SMT.isSat solver (Set.toList $ pat.constraints <> remainder)
210+
throw $
211+
RewriteRemainderPredicate [rule] satRes . coerce . foldl1 AndTerm $
212+
map coerce . Set.toList $
213+
remainder
202214
-- a single rule applies, see if it's special and return an appropriate result
203215
| labelOf rule `elem` cutLabels ->
204216
pure $ RewriteCutPoint (labelOf rule) (uniqueId rule) pat newPat
@@ -209,7 +221,6 @@ rewriteStep cutLabels terminalLabels pat = do
209221
AppliedRules (xs, remainder)
210222
-- multiple rules apply, analyse brunching and remainders
211223
| any isFalse remainder -> do
212-
withContext CtxRemainder $ logMessage ("remainder is UNSAT" :: Text)
213224
-- the remainder predicate is trivially false, return the branching result
214225
pure $
215226
RewriteBranch pat $
@@ -222,7 +233,6 @@ rewriteStep cutLabels terminalLabels pat = do
222233
SMT.isSat solver (Set.toList $ pat.constraints <> remainder) >>= \case
223234
SMT.IsUnsat -> do
224235
-- the remainder condition is unsatisfiable: no need to consider the remainder branch.
225-
withContext CtxRemainder $ logMessage ("remainder is UNSAT" :: Text)
226236
-- pure resultsWithoutRemainders
227237
pure $
228238
RewriteBranch pat $
@@ -438,6 +448,10 @@ applyRule pat@Pattern{ceilConditions} rule =
438448
case unclearRequiresAfterSmt of
439449
[] -> withPatternContext rewritten $ pure (rewritten, Predicate FalseBool, subst)
440450
_ -> do
451+
-- the requires clause was unclear:
452+
-- - add it as an assumption to the pattern
453+
-- - return it's negation as a rule remainder to construct
454+
--- the remainder pattern in @rewriteStep@
441455
let rewritten' = rewritten{constraints = rewritten.constraints <> Set.fromList unclearRequiresAfterSmt}
442456
in withPatternContext rewritten' $
443457
pure
@@ -502,8 +516,13 @@ applyRule pat@Pattern{ceilConditions} rule =
502516
solver <- lift $ RewriteT $ (.smtSolver) <$> ask
503517
SMT.checkPredicates solver pat.constraints mempty (Set.fromList stillUnclear) >>= \case
504518
SMT.IsUnknown reason -> do
505-
-- abort rewrite if a solver result was Unknown
506519
withContext CtxAbort $ logMessage reason
520+
-- return unclear rewrite rule condition if the condition is indeterminate
521+
withContext CtxConstraint . withContext CtxWarn . logMessage $
522+
WithJsonMessage (object ["conditions" .= (externaliseTerm . coerce <$> stillUnclear)]) $
523+
renderOneLineText $
524+
"Uncertain about condition(s) in a rule:"
525+
<+> (hsep . punctuate comma . map (pretty' @mods) $ stillUnclear)
507526
pure unclearRequires
508527
SMT.IsInvalid -> do
509528
-- requires is actually false given the prior

booster/library/Booster/SMT/Interface.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -232,7 +232,7 @@ showIsSatResult :: IsSatResult a -> Text
232232
showIsSatResult = \case
233233
IsSat{} -> "SAT"
234234
IsUnsat -> "UNSAT"
235-
IsUnknown{} -> "UNKNOWN"
235+
IsUnknown reason -> "UNKNOWN " <> (Text.pack . show $ reason)
236236

237237
{-# COMPLETE IsSat, IsUnsat, IsUnknown #-}
238238

0 commit comments

Comments
 (0)