@@ -64,6 +64,7 @@ import Prelude.Kore
6464import Control.Error
6565 ( MaybeT
6666 )
67+ import qualified Control.Monad as Monad
6768import Data.Bits
6869 ( complement
6970 , shift
@@ -97,6 +98,11 @@ import qualified Kore.Builtin.Builtin as Builtin
9798import Kore.Builtin.Int.Int
9899import qualified Kore.Domain.Builtin as Domain
99100import 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+ )
100106import Kore.Internal.TermLike as TermLike
101107import 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
0 commit comments