Skip to content

Commit 4066d2c

Browse files
Add built-in rule for symbolic ==Int (#1894)
1 parent 55ba4ef commit 4066d2c

File tree

2 files changed

+61
-1
lines changed

2 files changed

+61
-1
lines changed

kore/src/Kore/Builtin/Int.hs

Lines changed: 36 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -64,6 +64,7 @@ import Prelude.Kore
6464
import Control.Error
6565
( MaybeT
6666
)
67+
import qualified Control.Monad as Monad
6768
import Data.Bits
6869
( complement
6970
, shift
@@ -97,6 +98,11 @@ import qualified Kore.Builtin.Builtin as Builtin
9798
import Kore.Builtin.Int.Int
9899
import qualified Kore.Domain.Builtin as Domain
99100
import qualified Kore.Error
101+
import qualified Kore.Internal.Condition as Condition
102+
import qualified Kore.Internal.Pattern as Pattern
103+
import Kore.Internal.Predicate
104+
( makeCeilPredicate
105+
)
100106
import Kore.Internal.TermLike as TermLike
101107
import Kore.Step.Simplification.Simplify
102108
( BuiltinAndAxiomSimplifier
@@ -252,7 +258,7 @@ builtinFunctions =
252258

253259
, comparator gtKey (>)
254260
, comparator geKey (>=)
255-
, comparator eqKey (==)
261+
, (eqKey, Builtin.functionEvaluator evalEq)
256262
, comparator leKey (<=)
257263
, comparator ltKey (<)
258264
, comparator neKey (/=)
@@ -325,3 +331,32 @@ builtinFunctions =
325331
log2 n
326332
| n > 0 = Just (smallInteger (integerLog2# n))
327333
| otherwise = Nothing
334+
335+
evalEq :: Builtin.Function
336+
evalEq resultSort arguments@[_intLeft, _intRight] =
337+
concrete <|> symbolicReflexivity
338+
where
339+
concrete = do
340+
_intLeft <- expectBuiltinInt eqKey _intLeft
341+
_intRight <- expectBuiltinInt eqKey _intRight
342+
_intLeft == _intRight
343+
& Bool.asPattern resultSort
344+
& return
345+
346+
symbolicReflexivity = do
347+
Monad.guard (TermLike.isFunctionPattern _intLeft)
348+
-- Do not need to check _intRight because we only return a result
349+
-- when _intLeft and _intRight are equal.
350+
if _intLeft == _intRight then
351+
True & Bool.asPattern resultSort & returnPattern
352+
else
353+
empty
354+
355+
mkCeilUnlessDefined termLike
356+
| TermLike.isDefinedPattern termLike = Condition.topOf resultSort
357+
| otherwise =
358+
Condition.fromPredicate (makeCeilPredicate resultSort termLike)
359+
returnPattern = return . flip Pattern.andCondition conditions
360+
conditions = foldMap mkCeilUnlessDefined arguments
361+
362+
evalEq _ _ = Builtin.wrongArity eqKey

kore/test/Test/Kore/Builtin/Int.hs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,8 @@ module Test.Kore.Builtin.Int
1717
, test_unifyAnd_Equal
1818
, test_unifyAndEqual_Equal
1919
, test_unifyAnd_Fn
20+
, test_reflexivity_symbolic
21+
, test_symbolic_eq_not_conclusive
2022
, hprop_unparse
2123
--
2224
, asInternal
@@ -71,6 +73,7 @@ import Kore.Internal.TermLike
7173
import Test.Kore
7274
( elementVariableGen
7375
, standaloneGen
76+
, testId
7477
)
7578
import qualified Test.Kore.Builtin.Bool as Test.Bool
7679
import Test.Kore.Builtin.Builtin
@@ -444,6 +447,28 @@ test_unifyAnd_Fn =
444447
actual <- evaluateT $ mkAnd dv fnPat
445448
(===) expect actual
446449

450+
test_reflexivity_symbolic :: TestTree
451+
test_reflexivity_symbolic =
452+
testCaseWithSMT "evaluate symbolic reflexivity for equality" $ do
453+
let x = mkElemVar $ "x" `ofSort` intSort
454+
expect = Test.Bool.asPattern True
455+
actual <- evaluate $ mkApplySymbol eqIntSymbol [x, x]
456+
assertEqual' "" expect actual
457+
where
458+
ofSort :: Text.Text -> Sort -> ElementVariable VariableName
459+
ofSort idName sort = mkElementVariable (testId idName) sort
460+
461+
test_symbolic_eq_not_conclusive :: TestTree
462+
test_symbolic_eq_not_conclusive =
463+
testCaseWithSMT "evaluate symbolic equality for different variables" $ do
464+
let x = mkElemVar $ "x" `ofSort` intSort
465+
y = mkElemVar $ "y" `ofSort` intSort
466+
expect = fromTermLike $ mkApplySymbol eqIntSymbol [x, y]
467+
actual <- evaluate $ mkApplySymbol eqIntSymbol [x, y]
468+
assertEqual' "" expect actual
469+
where
470+
ofSort :: Text.Text -> Sort -> ElementVariable VariableName
471+
ofSort idName sort = mkElementVariable (testId idName) sort
447472

448473
hprop_unparse :: Property
449474
hprop_unparse = hpropUnparse (asInternal <$> genInteger)

0 commit comments

Comments
 (0)