Skip to content

Commit 9460590

Browse files
Simplify side conditions (#2393)
Co-authored-by: Thomas Tuegel <[email protected]>
1 parent a182994 commit 9460590

39 files changed

+1563
-1191
lines changed

kore/src/Kore/Attribute/Pattern.hs

Lines changed: 21 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -12,8 +12,9 @@ module Kore.Attribute.Pattern
1212
, mapVariables
1313
, traverseVariables
1414
, deleteFreeVariable
15-
, isFullySimplified
1615
, isSimplified
16+
, isSimplifiedAnyCondition
17+
, isSimplifiedSomeCondition
1718
, setSimplified
1819
, simplifiedAttribute
1920
, constructorLikeAttribute
@@ -63,12 +64,14 @@ import qualified Kore.Attribute.Pattern.FreeVariables as FreeVariables
6364
import Kore.Attribute.Pattern.Function
6465
import Kore.Attribute.Pattern.Functional
6566
import Kore.Attribute.Pattern.Simplified hiding
66-
( isFullySimplified
67-
, isSimplified
67+
( isSimplified
68+
, isSimplifiedAnyCondition
69+
, isSimplifiedSomeCondition
6870
)
6971
import qualified Kore.Attribute.Pattern.Simplified as Simplified
70-
( isFullySimplified
71-
, isSimplified
72+
( isSimplified
73+
, isSimplifiedAnyCondition
74+
, isSimplifiedSomeCondition
7275
)
7376
import Kore.Attribute.Synthetic
7477
import Kore.Debug
@@ -156,17 +159,26 @@ isSimplified sideCondition patt@Pattern {simplified} =
156159
assertSimplifiedConsistency patt
157160
$ Simplified.isSimplified sideCondition simplified
158161

162+
{- Checks whether the pattern is simplified relative to some side condition.
163+
-}
164+
isSimplifiedSomeCondition
165+
:: HasCallStack
166+
=> Pattern variable -> Bool
167+
isSimplifiedSomeCondition patt@Pattern {simplified} =
168+
assertSimplifiedConsistency patt
169+
$ Simplified.isSimplifiedSomeCondition simplified
170+
159171
{- Checks whether the pattern is simplified relative to any side condition.
160172
-}
161-
isFullySimplified :: HasCallStack => Pattern variable -> Bool
162-
isFullySimplified patt@Pattern {simplified} =
173+
isSimplifiedAnyCondition :: HasCallStack => Pattern variable -> Bool
174+
isSimplifiedAnyCondition patt@Pattern {simplified} =
163175
assertSimplifiedConsistency patt
164-
$ Simplified.isFullySimplified simplified
176+
$ Simplified.isSimplifiedAnyCondition simplified
165177

166178
assertSimplifiedConsistency :: HasCallStack => Pattern variable -> a -> a
167179
assertSimplifiedConsistency Pattern {constructorLike, simplified}
168180
| isConstructorLike constructorLike
169-
, not (Simplified.isFullySimplified simplified) =
181+
, not (Simplified.isSimplifiedAnyCondition simplified) =
170182
error "Inconsistent attributes, constructorLike implies fully simplified."
171183
| otherwise = id
172184

kore/src/Kore/Attribute/Pattern/Simplified.hs

Lines changed: 27 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,8 @@ module Kore.Attribute.Pattern.Simplified
1212
, pattern Simplified_
1313
, Type (..)
1414
, isSimplified
15-
, isFullySimplified
15+
, isSimplifiedAnyCondition
16+
, isSimplifiedSomeCondition
1617
, simplifiedTo
1718
, notSimplified
1819
, fullySimplified
@@ -225,6 +226,11 @@ Simplified_ _ Any `simplifiedTo` s@(Simplified_ Fully Any) = s
225226

226227
s1@(Simplified_ _ _) `simplifiedTo` s2@(Simplified_ Partly _) = s1 <> s2
227228

229+
{- | Is the pattern fully simplified under the given side condition?
230+
231+
See also: 'isSimplifiedAnyCondition', 'isSimplifiedSomeCondition'.
232+
233+
-}
228234
isSimplified :: SideCondition.Representation -> Simplified -> Bool
229235
isSimplified _ (Simplified_ Fully Any) = True
230236
isSimplified currentCondition (Simplified_ Fully (Condition condition)) =
@@ -233,12 +239,26 @@ isSimplified _ (Simplified_ Fully Unknown) = False
233239
isSimplified _ (Simplified_ Partly _) = False
234240
isSimplified _ NotSimplified = False
235241

236-
isFullySimplified :: Simplified -> Bool
237-
isFullySimplified (Simplified_ Fully Any) = True
238-
isFullySimplified (Simplified_ Fully (Condition _)) = False
239-
isFullySimplified (Simplified_ Fully Unknown) = False
240-
isFullySimplified (Simplified_ Partly _) = False
241-
isFullySimplified NotSimplified = False
242+
{- | Is the pattern fully simplified under any side condition?
243+
244+
See also: 'isSimplified', 'isSimplifiedSomeCondition'.
245+
246+
-}
247+
isSimplifiedAnyCondition :: Simplified -> Bool
248+
isSimplifiedAnyCondition (Simplified_ Fully Any) = True
249+
isSimplifiedAnyCondition (Simplified_ Fully (Condition _)) = False
250+
isSimplifiedAnyCondition (Simplified_ Fully Unknown) = False
251+
isSimplifiedAnyCondition (Simplified_ Partly _) = False
252+
isSimplifiedAnyCondition NotSimplified = False
253+
254+
{- | Is the pattern fully simplified under some side condition?
255+
256+
See also: 'isSimplified', 'isSimplifiedAnyCondition'.
257+
258+
-}
259+
isSimplifiedSomeCondition :: Simplified -> Bool
260+
isSimplifiedSomeCondition (Simplified_ Fully _) = True
261+
isSimplifiedSomeCondition _ = False
242262

243263
fullySimplified :: Simplified
244264
fullySimplified = Simplified_ Fully Any

kore/src/Kore/Attribute/PredicatePattern.hs

Lines changed: 22 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,8 @@ module Kore.Attribute.PredicatePattern
1111
-- simplified is excluded on purpose
1212
, simplifiedAttribute
1313
, isSimplified
14-
, isFullySimplified
14+
, isSimplifiedAnyCondition
15+
, isSimplifiedSomeCondition
1516
, setSimplified
1617
, mapVariables
1718
, traverseVariables
@@ -39,12 +40,14 @@ import qualified Kore.Attribute.Pattern.FreeVariables as FreeVariables
3940
( freeVariables
4041
)
4142
import Kore.Attribute.Pattern.Simplified hiding
42-
( isFullySimplified
43-
, isSimplified
43+
( isSimplified
44+
, isSimplifiedAnyCondition
45+
, isSimplifiedSomeCondition
4446
)
4547
import qualified Kore.Attribute.Pattern.Simplified as Simplified
46-
( isFullySimplified
47-
, isSimplified
48+
( isSimplified
49+
, isSimplifiedAnyCondition
50+
, isSimplifiedSomeCondition
4851
)
4952
import Kore.Attribute.Synthetic
5053
import Kore.Debug
@@ -97,12 +100,23 @@ isSimplified
97100
:: SideCondition.Representation -> PredicatePattern variable -> Bool
98101
isSimplified sideCondition = Simplified.isSimplified sideCondition . simplifiedAttribute
99102

103+
{- Checks whether the pattern is simplified relative to some side condition.
104+
-}
105+
isSimplifiedSomeCondition
106+
:: PredicatePattern variable -> Bool
107+
isSimplifiedSomeCondition =
108+
Simplified.isSimplifiedSomeCondition . simplifiedAttribute
109+
100110
{- Checks whether the pattern is simplified relative to any side condition.
101111
-}
102-
isFullySimplified :: PredicatePattern variable -> Bool
103-
isFullySimplified PredicatePattern {simplified} = Simplified.isFullySimplified simplified
112+
isSimplifiedAnyCondition :: PredicatePattern variable -> Bool
113+
isSimplifiedAnyCondition PredicatePattern {simplified} =
114+
Simplified.isSimplifiedAnyCondition simplified
104115

105-
setSimplified :: Simplified -> PredicatePattern variable -> PredicatePattern variable
116+
setSimplified
117+
:: Simplified
118+
-> PredicatePattern variable
119+
-> PredicatePattern variable
106120
setSimplified simplified patt = patt { simplified }
107121

108122
{- | Use the provided mapping to replace all variables in a 'Pattern'.

kore/src/Kore/Equation/Simplification.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -37,9 +37,6 @@ import Kore.Internal.Pattern
3737
)
3838
import qualified Kore.Internal.Pattern as Pattern
3939
import qualified Kore.Internal.Predicate as Predicate
40-
import qualified Kore.Internal.SideCondition as SideCondition
41-
( top
42-
)
4340
import qualified Kore.Internal.Substitution as Substitution
4441
import qualified Kore.Internal.TermLike as TermLike
4542
import qualified Kore.Step.Simplification.Pattern as Pattern
@@ -134,4 +131,4 @@ simplifyPattern
134131
-> simplifier (OrPattern variable)
135132
simplifyPattern patt =
136133
Simplifier.localSimplifierAxioms (const mempty)
137-
$ Pattern.simplify SideCondition.top patt
134+
$ Pattern.simplify patt

kore/src/Kore/Exec.hs

Lines changed: 3 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -92,9 +92,6 @@ import Kore.Internal.Predicate
9292
, makeMultipleOrPredicate
9393
)
9494
import qualified Kore.Internal.SideCondition as SideCondition
95-
( top
96-
, topTODO
97-
)
9895
import Kore.Internal.TermLike
9996
import Kore.Log.ErrorRewriteLoop
10097
( errorRewriteLoop
@@ -224,8 +221,7 @@ exec depthLimit breadthLimit verifiedModule strategy initialTerm =
224221
finals <-
225222
getFinalConfigsOf $ do
226223
initialConfig <-
227-
Pattern.simplify SideCondition.top
228-
(Pattern.fromTermLike initialTerm)
224+
Pattern.simplify (Pattern.fromTermLike initialTerm)
229225
>>= Logic.scatter
230226
let
231227
updateQueue = \as ->
@@ -372,8 +368,7 @@ search depthLimit breadthLimit verifiedModule termLike searchPattern searchConfi
372368
initialized <- initializeAndSimplify verifiedModule
373369
let Initialized { rewriteRules } = initialized
374370
simplifiedPatterns <-
375-
Pattern.simplify SideCondition.top
376-
$ Pattern.fromTermLike termLike
371+
Pattern.simplify $ Pattern.fromTermLike termLike
377372
let
378373
initialPattern =
379374
case toList simplifiedPatterns of
@@ -401,7 +396,7 @@ search depthLimit breadthLimit verifiedModule termLike searchPattern searchConfi
401396
searchGraph
402397
searchConfig
403398
(match
404-
SideCondition.topTODO
399+
SideCondition.top
405400
(mkRewritingPattern searchPattern)
406401
)
407402
executionGraph

kore/src/Kore/Internal/OrPattern.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Kore.Internal.OrPattern
88
, coerceSort
99
, isSimplified
1010
, hasSimplifiedChildren
11+
, hasSimplifiedChildrenIgnoreConditions
1112
, forgetSimplified
1213
, fromPatterns
1314
, toPatterns
@@ -95,6 +96,18 @@ hasSimplifiedChildren
9596
hasSimplifiedChildren sideCondition =
9697
all (Pattern.hasSimplifiedChildren sideCondition)
9798

99+
{- | Checks whether all patterns in the disjunction have simplified children,
100+
ignoring the conditions used to simplify them.
101+
102+
See also: 'Pattern.hasSimplifiedChildrenIgnoreConditions'
103+
104+
-}
105+
hasSimplifiedChildrenIgnoreConditions
106+
:: InternalVariable variable
107+
=> OrPattern variable -> Bool
108+
hasSimplifiedChildrenIgnoreConditions =
109+
all Pattern.hasSimplifiedChildrenIgnoreConditions
110+
98111
forgetSimplified
99112
:: InternalVariable variable => OrPattern variable -> OrPattern variable
100113
forgetSimplified = fromPatterns . map Pattern.forgetSimplified . toPatterns

kore/src/Kore/Internal/Pattern.hs

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ module Kore.Internal.Pattern
2626
, Kore.Internal.Pattern.freeElementVariables
2727
, isSimplified
2828
, hasSimplifiedChildren
29+
, hasSimplifiedChildrenIgnoreConditions
2930
, forgetSimplified
3031
, markSimplified
3132
, simplifiedAttribute
@@ -162,6 +163,20 @@ hasSimplifiedChildren sideCondition patt =
162163
Conditional { term, predicate, substitution } = patt
163164
clauses = MultiAnd.fromPredicate predicate
164165

166+
{- | Similar to 'hasSimplifiedChildren', only that it ignores the conditions
167+
used to simplify the children.
168+
-}
169+
hasSimplifiedChildrenIgnoreConditions
170+
:: Ord variable
171+
=> Pattern variable -> Bool
172+
hasSimplifiedChildrenIgnoreConditions patt =
173+
TermLike.isSimplifiedSomeCondition term
174+
&& all Predicate.isSimplifiedSomeCondition clauses
175+
&& Substitution.isSimplifiedSomeCondition substitution
176+
where
177+
Conditional { term, predicate, substitution } = patt
178+
clauses = MultiAnd.fromPredicate predicate
179+
165180
forgetSimplified
166181
:: InternalVariable variable => Pattern variable -> Pattern variable
167182
forgetSimplified patt =

kore/src/Kore/Internal/Predicate.hs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ module Kore.Internal.Predicate
3535
, isPredicate
3636
, simplifiedAttribute
3737
, isSimplified
38+
, isSimplifiedSomeCondition
3839
, isFreeOf
3940
, freeElementVariables
4041
, hasFreeVariable
@@ -142,6 +143,7 @@ import Kore.Internal.TermLike hiding
142143
, forgetSimplified
143144
, hasFreeVariable
144145
, isSimplified
146+
, isSimplifiedSomeCondition
145147
, mapVariables
146148
, markSimplified
147149
, markSimplifiedConditional
@@ -911,9 +913,23 @@ instance HasFreeVariables (Predicate variable) variable where
911913
simplifiedAttribute :: Predicate variable -> Simplified
912914
simplifiedAttribute = Attribute.simplifiedAttribute . extractAttributes
913915

916+
{- | Is the 'Predicate' fully simplified under the given side condition?
917+
918+
See also: 'isSimplifiedSomeCondition'.
919+
920+
-}
914921
isSimplified :: SideCondition.Representation -> Predicate variable -> Bool
915922
isSimplified condition = Attribute.isSimplified condition . extractAttributes
916923

924+
{- | Is the 'Predicate' fully simplified under some side condition?
925+
926+
See also: 'isSimplified'.
927+
928+
-}
929+
isSimplifiedSomeCondition :: Predicate variable -> Bool
930+
isSimplifiedSomeCondition =
931+
Attribute.isSimplifiedSomeCondition . extractAttributes
932+
917933
cannotSimplifyNotSimplifiedError
918934
:: (HasCallStack, InternalVariable variable)
919935
=> PredicateF variable (Predicate variable) -> a

kore/src/Kore/Internal/SideCondition/SideCondition.hs

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,14 @@ module Kore.Internal.SideCondition.SideCondition
99
) where
1010

1111
import Prelude.Kore
12+
import Pretty
13+
( Pretty (..)
14+
)
1215

1316
import Data.Hashable
1417
( Hashed
1518
, hashed
19+
, unhashed
1620
)
1721

1822
import Data.Type.Equality
@@ -30,7 +34,7 @@ import Type.Reflection
3034
)
3135

3236
data Representation where
33-
Representation :: Ord a => !(TypeRep a) -> !(Hashed a) -> Representation
37+
Representation :: (Ord a, Pretty a) => !(TypeRep a) -> !(Hashed a) -> Representation
3438

3539
instance Eq Representation where
3640
(==) (Representation typeRep1 hashed1) (Representation typeRep2 hashed2) =
@@ -64,9 +68,12 @@ instance NFData Representation where
6468
rnf (Representation typeRep1 hashed1) = typeRep1 `seq` hashed1 `seq` ()
6569
{-# INLINE rnf #-}
6670

71+
instance Pretty Representation where
72+
pretty (Representation _ h) = pretty (unhashed h)
73+
6774
-- | Creates a 'Representation'. Should not be used directly.
6875
-- See 'Kore.Internal.SideCondition.toRepresentation'.
69-
mkRepresentation :: (Ord a, Hashable a, Typeable a) => a -> Representation
76+
mkRepresentation :: (Ord a, Hashable a, Typeable a, Pretty a) => a -> Representation
7077
mkRepresentation = Representation typeRep . hashed
7178

7279
instance Debug Representation where

0 commit comments

Comments
 (0)