Skip to content

Commit d5436e7

Browse files
authored
Bug fix for symbolic narrowing (#1997)
* test_narrowing: Tests for symbolic narrowing * Kore.Internal.Substitution.substitute * Kore.Internal.Pattern.substitute * getResultPattern: Apply renaming to right-hand side of substitution The renaming from rule to (fresh) configuration variables is also applied to the right-hand side of the substitution. The renaming was already applied to the term and predicate, but the substitution was overlooked. This fixes a bug that manifests when narrowing a symbolic configuration into another symbolic configuration. * test_narrowing: Also check remainders * CHANGELOG * Kore.Internal.Pattern.substitute: Note about denormalized Substitution
1 parent e764355 commit d5436e7

File tree

7 files changed

+134
-10
lines changed

7 files changed

+134
-10
lines changed

kore/CHANGELOG.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,9 @@ All notable changes to this project will be documented in this file.
1414

1515
### Fixed
1616

17+
- A bug is fixed where variables introduced by symbolic narrowing could be
18+
captured incorrectly.
19+
1720
## [0.25.0.0] - 2020-07-08
1821

1922
### Added

kore/src/Kore/Internal/Pattern.hs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ module Kore.Internal.Pattern
2828
, simplifiedAttribute
2929
, assign
3030
, requireDefined
31+
, substitute
3132
-- * Re-exports
3233
, Conditional (..)
3334
, Conditional.andCondition
@@ -40,6 +41,10 @@ module Kore.Internal.Pattern
4041

4142
import Prelude.Kore
4243

44+
import Data.Map.Strict
45+
( Map
46+
)
47+
4348
import Kore.Attribute.Pattern.FreeVariables
4449
( freeVariables
4550
, getFreeElementVariables
@@ -350,3 +355,20 @@ requireDefined Conditional { term, predicate, substitution } =
350355
}
351356
where
352357
sort = termLikeSort term
358+
359+
{- | Apply a normalized 'Substitution' to a 'Pattern'.
360+
361+
The 'Substitution' of the result will not be normalized.
362+
363+
-}
364+
substitute
365+
:: InternalVariable variable
366+
=> Map (SomeVariableName variable) (TermLike variable)
367+
-> Pattern variable
368+
-> Pattern variable
369+
substitute subst Conditional { term, predicate, substitution } =
370+
Conditional
371+
{ term = TermLike.substitute subst term
372+
, predicate = Predicate.substitute subst predicate
373+
, substitution = Substitution.substitute subst substitution
374+
}

kore/src/Kore/Internal/Substitution.hs

Lines changed: 18 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ module Kore.Internal.Substitution
4646
, wrapNormalization
4747
, mkNormalization
4848
, applyNormalized
49+
, substitute
4950
) where
5051

5152
import Prelude.Kore hiding
@@ -702,16 +703,30 @@ applyNormalized
702703
applyNormalized Normalization { normalized, denormalized } =
703704
Normalization
704705
{ normalized
705-
, denormalized =
706-
mapAssignedTerm substitute <$> denormalized
706+
, denormalized = mapAssignedTerm substitute' <$> denormalized
707707
}
708708
where
709-
substitute =
709+
substitute' =
710710
TermLike.substitute
711711
$ Map.mapKeys variableName
712712
$ Map.fromList
713713
$ map assignmentToPair normalized
714714

715+
{- | Apply a 'Map' from names to terms to a substitution.
716+
717+
The given mapping will be applied only to the right-hand sides of the
718+
substitutions (see 'mapAssignedTerm'). The result will not be a normalized
719+
'Substitution'.
720+
721+
-}
722+
substitute
723+
:: InternalVariable variable
724+
=> Map (SomeVariableName variable) (TermLike variable)
725+
-> Substitution variable
726+
-> Substitution variable
727+
substitute subst =
728+
wrap . (map . mapAssignedTerm) (TermLike.substitute subst) . unwrap
729+
715730
{- | @toPredicate@ constructs a 'Predicate' equivalent to 'Substitution'.
716731
717732
An empty substitution list returns a true predicate. A non-empty substitution

kore/src/Kore/Rewriting/RewritingVariable.hs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -210,11 +210,7 @@ getResultPattern initial config@Conditional { substitution } =
210210
. Map.map (TermLike.mkVar . mkUnifiedConfigVariable)
211211
$ refreshVariables avoiding introduced
212212
renamed :: Pattern RewritingVariableName
213-
renamed =
214-
filtered
215-
{ term = TermLike.substitute renaming (term filtered)
216-
, predicate = Predicate.substitute renaming (predicate filtered)
217-
}
213+
renamed = filtered & Pattern.substitute renaming
218214

219215
{- | Prepare a rule for unification or matching with the configuration.
220216

kore/test/Test/Kore/Internal/Pattern.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ import Test.Kore.Internal.TermLike hiding
3030
, mapVariables
3131
, markSimplified
3232
, simplifiedAttribute
33+
, substitute
3334
)
3435
import Test.Kore.Variables.V
3536
import Test.Kore.Variables.W

kore/test/Test/Kore/Internal/Substitution.hs

Lines changed: 36 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,11 @@
11
module Test.Kore.Internal.Substitution
22
( test_substitution
33
, test_toPredicate
4+
, test_substitute
45
-- * Re-exports
56
, TestAssignment
67
, TestSubstitution
7-
, module Kore.Internal.Substitution
8+
, module Substitution
89
, module Test.Kore.Internal.TermLike
910
) where
1011

@@ -14,9 +15,10 @@ import Prelude.Kore hiding
1415

1516
import Test.Tasty
1617

18+
import qualified Data.Map.Strict as Map
1719
import qualified Data.Set as Set
1820

19-
import Kore.Internal.Substitution
21+
import Kore.Internal.Substitution as Substitution
2022
import Kore.TopBottom
2123
( isBottom
2224
, isTop
@@ -39,6 +41,8 @@ import Test.Kore.Internal.TermLike hiding
3941
, mapVariables
4042
, markSimplified
4143
, simplifiedAttribute
44+
, substitute
45+
, test_substitute
4246
)
4347
import qualified Test.Kore.Step.MockSymbols as Mock
4448
import Test.Tasty.HUnit.Ext
@@ -361,3 +365,33 @@ pr1 =
361365
a, b :: Sort -> ElementVariable'
362366
a = fmap ElementVariableName . Variable (VariableName (testId "a") mempty)
363367
b = fmap ElementVariableName . Variable (VariableName (testId "b") mempty)
368+
369+
test_substitute :: [TestTree]
370+
test_substitute =
371+
[ testGroup "is denormalized"
372+
[ testCase "Denormalized" $ do
373+
let input = wrap [assign (inject Mock.x) Mock.a]
374+
actual = Substitution.substitute Map.empty input
375+
assertDenormalized actual
376+
, testCase "Normalized" $ do
377+
let input = unsafeWrap [(inject Mock.x, Mock.a)]
378+
actual = Substitution.substitute Map.empty input
379+
assertDenormalized actual
380+
]
381+
, testCase "applies to right-hand side" $ do
382+
let input = wrap [assign (inject Mock.x) (Mock.f (mkElemVar Mock.y))]
383+
subst = Map.singleton (inject $ variableName Mock.y) Mock.a
384+
expect = wrap [assign (inject Mock.x) (Mock.f Mock.a)]
385+
actual = Substitution.substitute subst input
386+
assertEqual "" expect actual
387+
, testCase "does not apply to left-hand side" $ do
388+
let input = wrap [assign (inject Mock.x) (Mock.f (mkElemVar Mock.y))]
389+
subst = Map.singleton (inject $ variableName Mock.x) Mock.a
390+
expect = input
391+
actual = Substitution.substitute subst input
392+
assertEqual "" expect actual
393+
]
394+
395+
assertDenormalized :: HasCallStack => Substitution VariableName -> Assertion
396+
assertDenormalized =
397+
assertBool "expected denormalized substitution" . (not . isNormalized)

kore/test/Test/Kore/Step/RewriteStep.hs

Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Test.Kore.Step.RewriteStep
55
, test_applyRewriteRule_
66
, test_applyRewriteRulesParallel
77
, test_applyRewriteRulesSequence
8+
, test_narrowing
89
) where
910

1011
import Prelude.Kore
@@ -41,6 +42,7 @@ import Kore.Internal.Predicate as Predicate
4142
, makeTruePredicate
4243
, makeTruePredicate_
4344
)
45+
import qualified Kore.Internal.Predicate as Predicate
4446
import qualified Kore.Internal.Substitution as Substitution
4547
import Kore.Internal.TermLike
4648
import Kore.Rewriting.RewritingVariable
@@ -738,6 +740,57 @@ test_applyRewriteRule_ =
738740
)
739741
(Mock.sigma (mkElemVar Mock.x) (mkElemVar Mock.y))
740742

743+
{- | Tests for symbolic narrowing.
744+
745+
Narrowing happens when a variable in a symbolic configuration is instantiated
746+
with a particular value.
747+
748+
-}
749+
test_narrowing :: [TestTree]
750+
test_narrowing =
751+
[ testCase "applyRewriteRulesParallel" $ do
752+
actual <- apply axiom (Pattern.fromTermLike initial)
753+
let results = OrPattern.fromPatterns [result]
754+
checkResults results actual
755+
let remainders = OrPattern.fromPatterns [remainder]
756+
checkRemainders remainders actual
757+
, testCase "getResultPattern" $ do
758+
let resultRewriting =
759+
Pattern.withCondition (Mock.sigma Mock.b (mkElemVar xRule))
760+
$ Condition.fromSingleSubstitution
761+
$ Substitution.assign
762+
(inject xConfig)
763+
(Mock.sigma Mock.a (mkElemVar xRule))
764+
initialVariables = FreeVariables.freeVariable (inject xConfig)
765+
actual = getResultPattern initialVariables resultRewriting
766+
assertEqual "" result actual
767+
]
768+
where
769+
apply rule config = applyRewriteRulesParallel config [rule]
770+
x = Mock.x
771+
x' = traverse (\name -> nextName name name) x & fromJust
772+
xConfig = mkElementConfigVariable x
773+
xRule = mkElementRuleVariable x
774+
initial = mkElemVar x
775+
-- The significance of this axiom is that it narrows the initial term and
776+
-- introduces a new variable.
777+
axiom =
778+
RewriteRule $ rulePattern
779+
(Mock.sigma Mock.a (mkElemVar x))
780+
(Mock.sigma Mock.b (mkElemVar x))
781+
result =
782+
Pattern.withCondition (Mock.sigma Mock.b (mkElemVar x'))
783+
$ Condition.fromSingleSubstitution
784+
$ Substitution.assign (inject x) (Mock.sigma Mock.a (mkElemVar x'))
785+
remainder =
786+
Pattern.withCondition initial
787+
$ Condition.fromPredicate
788+
$ Predicate.makeNotPredicate
789+
$ Predicate.makeExistsPredicate x'
790+
$ Predicate.makeEqualsPredicate_
791+
(mkElemVar x)
792+
(Mock.sigma Mock.a (mkElemVar x'))
793+
741794
-- | Apply the 'RewriteRule's to the configuration.
742795
applyRewriteRulesParallel
743796
:: TestPattern

0 commit comments

Comments
 (0)