Skip to content

Commit c35bfa5

Browse files
ana-pantiliettuegelrv-jenkins
authored
Remove defined marker (#2380)
* Add HashMap to SideCondition * Rename assumptions to replacements * Use simplifyConjunctionWithAssumptions to construct and combine SideCondition * Hlint * Use to and from SideCondition to simplify Condition * Use Changed in simplifyConjunctions again * Use replacements when simplifying terms, with exception * Regenerate golden * Comment out failing test, TODO fix * Simplify Pattern with SideCondition in only special cases * Use simplify instead of simplifyTopConfiguration * Modify test which describes possibly wrong behavior * Fixed onepath test * TermLike.simplify unit tests; simplify with all replacements * Remove unused imports * Add Pretty instance for SideCondition * Add documentation * Add strictness to fields * Add strict language pragma * Make lazy binding * Address review comments * Clean-up * Update kore/src/Kore/Step/Simplification/Condition.hs Co-authored-by: Thomas Tuegel <[email protected]> * Update Debug.hs * Modify simplification in checkImplication * unifyKequalsEq should apply for both \and and \equals * Tests for KEqual unification * Add a HashSet of defined TermLikes to SideCondition * Draft, incomplete implementation of assumeDefined * Implement assumeDefined for assoc comm collections * Fix * Fixes and tests for generateNormalizedAcs * Tests and fixes * Keep term and predicate replacements together as terms * Remove double import * generateNormalizedAcs: clean-up * Finish isDefined, add tests and clean-up * Major test clean-up, include set tests * Fix functional application case, add tests * Remove Defined marker * Materialize Nix expressions * Propagate side condition in SMT translator * Use definedness in translatePattern as well * Add tests for defined SMT translation back * Remove unused test module * Get rid of isDefinedPattern in Matcher * Materialize Nix expressions * Carry SideCondition in Builtin modules; replace isDefinedPattern * Remove rest of Defined node * Fix isDefined case for 1-element, 1-opaque collections * Add accidentally removed collection unification cases * Temp: TODO and debugging info * Fix unit test bugs * SideCondition, Pattern: clean-up and documentation * Add unit tests for values definedness * Update TODO comment Co-authored-by: Thomas Tuegel <[email protected]> * Update kore/src/Kore/Step/Simplification/Exists.hs Co-authored-by: Thomas Tuegel <[email protected]> * Address review comment Co-authored-by: Thomas Tuegel <[email protected]> Co-authored-by: ana-pantilie <[email protected]> Co-authored-by: rv-jenkins <[email protected]>
1 parent 4195d94 commit c35bfa5

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

44 files changed

+477
-1108
lines changed

kore/kore.cabal

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ cabal-version: 2.2
44
--
55
-- see: https://github.com/sol/hpack
66
--
7-
-- hash: 80d27d36f0343e3b6779aa37ed5fccc747fd7c1b66c7b9bd2fb27c1f6a2d6403
7+
-- hash: f665c212513ddd12eaa511bf198ce16f125dd902b5b25a656b2fa584d073c5ba
88

99
name: kore
1010
version: 0.41.0.0
@@ -284,7 +284,6 @@ library
284284
Kore.Step.Simplification.CeilSimplifier
285285
Kore.Step.Simplification.Condition
286286
Kore.Step.Simplification.Data
287-
Kore.Step.Simplification.Defined
288287
Kore.Step.Simplification.DomainValue
289288
Kore.Step.Simplification.Equals
290289
Kore.Step.Simplification.Exists
@@ -930,7 +929,6 @@ test-suite kore-test
930929
Test.Kore.BugReport
931930
Test.Kore.Builtin
932931
Test.Kore.Builtin.AssocComm.CeilSimplifier
933-
Test.Kore.Builtin.AssociativeCommutative
934932
Test.Kore.Builtin.Bool
935933
Test.Kore.Builtin.Builtin
936934
Test.Kore.Builtin.Definition

kore/src/Kore/Builtin/AssociativeCommutative.hs

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -108,7 +108,6 @@ import Kore.Internal.Symbol
108108
)
109109
import Kore.Internal.TermLike
110110
( pattern App_
111-
, pattern Defined_
112111
, pattern ElemVar_
113112
, pattern InternalMap_
114113
, pattern InternalSet_
@@ -220,7 +219,6 @@ instance TermWrapper NormalizedMap where
220219

221220
matchBuiltin (InternalMap_ internalMap) =
222221
Just (builtinAcChild internalMap)
223-
matchBuiltin (Defined_ child) = matchBuiltin child
224222
matchBuiltin _ = Nothing
225223

226224
{- |Transforms a @TermLike@ representation into a @NormalizedOrBottom@.
@@ -262,7 +260,6 @@ instance TermWrapper NormalizedMap where
262260
case args of
263261
[map1, map2] -> toNormalized map1 <> toNormalized map2
264262
_ -> Builtin.wrongArity "MAP.concat"
265-
toNormalized (Defined_ child) = toNormalized child
266263
toNormalized patt =
267264
(Normalized . wrapAc) NormalizedAc
268265
{ elementsWithVariables = []
@@ -357,8 +354,6 @@ toNormalizedInternalMapWorker term@(App_ symbol args)
357354
}
358355
return internal
359356
_ -> Builtin.wrongArity "MAP.concat"
360-
toNormalizedInternalMapWorker (Defined_ child) =
361-
toNormalizedInternalMapWorker child
362357
toNormalizedInternalMapWorker term =
363358
Just (emptyInternalAc @NormalizedMap (termLikeSort term))
364359
{ builtinAcChild = wrapAc emptyNormalizedAc { opaque = [term] }
@@ -386,7 +381,6 @@ instance TermWrapper NormalizedSet where
386381

387382
matchBuiltin (InternalSet_ internalSet) =
388383
Just (builtinAcChild internalSet)
389-
matchBuiltin (Defined_ child) = matchBuiltin child
390384
matchBuiltin _ = Nothing
391385

392386
{- |Transforms a @TermLike@ representation into a @NormalizedSetOrBottom@.
@@ -427,7 +421,6 @@ instance TermWrapper NormalizedSet where
427421
case args of
428422
[set1, set2] -> toNormalized set1 <> toNormalized set2
429423
_ -> Builtin.wrongArity "SET.concat"
430-
toNormalized (Defined_ child) = toNormalized child
431424
toNormalized patt =
432425
(Normalized . wrapAc)
433426
emptyNormalizedAc { opaque = [patt] }
@@ -520,8 +513,6 @@ toNormalizedInternalSetWorker term@(App_ symbol args)
520513
}
521514
return internal
522515
_ -> Builtin.wrongArity "SET.concat"
523-
toNormalizedInternalSetWorker (Defined_ child) =
524-
toNormalizedInternalSetWorker child
525516
toNormalizedInternalSetWorker term =
526517
Just (emptyInternalAc @NormalizedSet (termLikeSort term))
527518
{ builtinAcChild = wrapAc emptyNormalizedAc { opaque = [term] }

kore/src/Kore/Builtin/Builtin.hs

Lines changed: 17 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,9 @@ import Kore.Internal.Predicate
9595
( makeEqualsPredicate
9696
)
9797
import qualified Kore.Internal.Predicate as Predicate
98+
import Kore.Internal.SideCondition
99+
( SideCondition
100+
)
98101
import qualified Kore.Internal.SideCondition as SideCondition
99102
( topTODO
100103
)
@@ -180,7 +183,7 @@ unaryOperator extractVal asPattern ctx op =
180183
get = extractVal ctx
181184

182185
unaryOperator0 :: Function
183-
unaryOperator0 resultSort children =
186+
unaryOperator0 _ resultSort children =
184187
case children of
185188
[termLike]
186189
| Just a <- get termLike -> do
@@ -220,7 +223,7 @@ binaryOperator extractVal asPattern ctx op =
220223
get = extractVal ctx
221224

222225
binaryOperator0 :: Function
223-
binaryOperator0 resultSort children =
226+
binaryOperator0 _ resultSort children =
224227
case children of
225228
[get -> Just a, get -> Just b] -> do
226229
-- Apply the operator to two domain values
@@ -259,7 +262,7 @@ ternaryOperator extractVal asPattern ctx op =
259262
get = extractVal ctx
260263

261264
ternaryOperator0 :: Function
262-
ternaryOperator0 resultSort children =
265+
ternaryOperator0 _ resultSort children =
263266
case children of
264267
[get -> Just a, get -> Just b, get -> Just c] -> do
265268
-- Apply the operator to three domain values
@@ -273,23 +276,25 @@ type Function
273276
. InternalVariable variable
274277
=> HasCallStack
275278
=> MonadSimplify simplifier
276-
=> Sort
279+
=> SideCondition variable
280+
-> Sort
277281
-> [TermLike variable]
278282
-> MaybeT simplifier (Pattern variable)
279283

280284
functionEvaluator :: Function -> BuiltinAndAxiomSimplifier
281285
functionEvaluator impl =
282-
applicationEvaluator $ \app -> do
286+
applicationEvaluator $ \sideCondition app -> do
283287
let Application { applicationSymbolOrAlias = symbol } = app
284288
Application { applicationChildren = args } = app
285289
resultSort = symbolSorts symbol & applicationSortsResult
286-
impl resultSort args
290+
impl sideCondition resultSort args
287291

288292
applicationEvaluator
289293
:: ( forall variable simplifier
290294
. InternalVariable variable
291295
=> MonadSimplify simplifier
292-
=> Application Symbol (TermLike variable)
296+
=> SideCondition variable
297+
-> Application Symbol (TermLike variable)
293298
-> MaybeT simplifier (Pattern variable)
294299
)
295300
-> BuiltinAndAxiomSimplifier
@@ -299,14 +304,16 @@ applicationEvaluator impl =
299304
evaluator
300305
:: InternalVariable variable
301306
=> MonadSimplify simplifier
302-
=> CofreeF
307+
=> SideCondition variable
308+
-> CofreeF
303309
(Application Symbol)
304310
(Attribute.Pattern variable)
305311
(TermLike variable)
306312
-> simplifier (AttemptedAxiom variable)
307-
evaluator (_ :< app) = do
313+
evaluator sideCondition (_ :< app) = do
308314
let app' = fmap TermLike.removeEvaluated app
309-
getAttemptedAxiom (impl app' >>= appliedFunction)
315+
getAttemptedAxiom
316+
(impl sideCondition app' >>= appliedFunction)
310317

311318
{- | Run a parser on a verified domain value.
312319

kore/src/Kore/Builtin/External.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -137,10 +137,6 @@ externalize =
137137
$ mapHead Symbol.toSymbolOrAlias
138138
$ Signedness.toApplication
139139
$ getConst signednessF
140-
DefinedF definedF ->
141-
Cofree.tailF
142-
$ worker
143-
$ getDefined definedF
144140
InjF _ -> error "Unexpected sort injection"
145141
InternalBoolF _ -> error "Unexpected internal builtin"
146142
InternalBytesF _ -> error "Unexpected internal builtin"

kore/src/Kore/Builtin/Int.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,7 @@ import qualified Kore.Internal.Pattern as Pattern
120120
import Kore.Internal.Predicate
121121
( makeCeilPredicate
122122
)
123+
import qualified Kore.Internal.SideCondition as SideCondition
123124
import Kore.Internal.Symbol
124125
( symbolHook
125126
)
@@ -368,7 +369,7 @@ powmod b e m
368369
| otherwise = Just (powModInteger b e m)
369370

370371
evalEq :: Builtin.Function
371-
evalEq resultSort arguments@[_intLeft, _intRight] =
372+
evalEq sideCondition resultSort arguments@[_intLeft, _intRight] =
372373
concrete <|> symbolicReflexivity
373374
where
374375
concrete = do
@@ -388,13 +389,13 @@ evalEq resultSort arguments@[_intLeft, _intRight] =
388389
empty
389390

390391
mkCeilUnlessDefined termLike
391-
| TermLike.isDefinedPattern termLike = Condition.top
392+
| SideCondition.isDefined sideCondition termLike = Condition.top
392393
| otherwise =
393394
Condition.fromPredicate (makeCeilPredicate termLike)
394395
returnPattern = return . flip Pattern.andCondition conditions
395396
conditions = foldMap mkCeilUnlessDefined arguments
396397

397-
evalEq _ _ = Builtin.wrongArity eqKey
398+
evalEq _ _ _ = Builtin.wrongArity eqKey
398399

399400
{- | Match the @INT.eq@ hooked symbol.
400401
-}

0 commit comments

Comments
 (0)