Skip to content

Commit f4d56bd

Browse files
ana-pantiliegithub-actionsMirceaSrv-jenkins
authored
Cache simplified functions in SideCondition (#2662)
* WIP: keep and use metadata of simplified functions in SideCondition * Format with fourmolu * Cache when doing proof rewrites * Format with fourmolu * Move call to cacheSimplified.. at the top * Format with fourmolu * Update golden file * SideCondition.Representation: remove simplifiedFunctions * Format with fourmolu * Revert change to integration test * Clean-up and documentation * Format with fourmolu * Add unit tests * Format with fourmolu * Revert changes to AllPathClaim * Factor out recursive call Co-authored-by: Octavian Mircea Sebe <[email protected]> Co-authored-by: github-actions <[email protected]> Co-authored-by: Octavian Mircea Sebe <[email protected]> Co-authored-by: rv-jenkins <[email protected]>
1 parent 3173ec4 commit f4d56bd

File tree

7 files changed

+458
-136
lines changed

7 files changed

+458
-136
lines changed

kore/src/Kore/Internal/SideCondition.hs

Lines changed: 160 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,9 @@ module Kore.Internal.SideCondition (
2525
fromDefinedTerms,
2626
generateNormalizedAcs,
2727
simplifyConjunctionByAssumption,
28+
cacheSimplifiedFunctions,
29+
isSimplifiedFunction,
30+
fromSimplifiedFunctions,
2831
) where
2932

3033
import Changed
@@ -96,11 +99,13 @@ import Kore.Internal.Predicate (
9699
import qualified Kore.Internal.Predicate as Predicate
97100
import Kore.Internal.SideCondition.SideCondition as SideCondition
98101
import Kore.Internal.Symbol (
102+
Symbol,
99103
isConstructor,
100104
isFunction,
101105
isFunctional,
102106
)
103107
import Kore.Internal.TermLike (
108+
Application,
104109
Key,
105110
TermLike,
106111
pattern App_,
@@ -140,9 +145,12 @@ import qualified SQL
140145

141146
{- | Side condition used in the evaluation context.
142147
143-
It contains a predicate assumed to be true, and a table of term replacements,
144-
which is used when simplifying terms. The table is constructed from the predicate,
145-
see 'simplifyConjunctionByAssumption'.
148+
It contains:
149+
* a predicate assumed to be true
150+
* a table of term replacements which is used when simplifying terms
151+
* a set of terms which are assumed to be defined
152+
* a set of terms with function application at the top which are known to have been
153+
simplified as much as possible during the current rewrite step
146154
147155
Warning! When simplifying a pattern, extra care should be taken that the
148156
'SideCondition' sent to the simplifier isn't created from the same 'Condition'
@@ -158,6 +166,8 @@ data SideCondition variable = SideCondition
158166
, replacementsPredicate ::
159167
!(HashMap (Predicate variable) (Predicate variable))
160168
, definedTerms :: !(HashSet (TermLike variable))
169+
, simplifiedFunctions ::
170+
!(HashSet (Application Symbol (TermLike variable)))
161171
}
162172
deriving stock (Eq, Ord, Show)
163173
deriving stock (GHC.Generic)
@@ -170,11 +180,14 @@ instance InternalVariable variable => SQL.Column (SideCondition variable) where
170180
toColumn = SQL.toColumn . Pretty.renderText . Pretty.layoutOneLine . pretty
171181

172182
instance Ord variable => HasFreeVariables (SideCondition variable) variable where
173-
freeVariables sideCondition@(SideCondition _ _ _ _) =
183+
freeVariables sideCondition@(SideCondition _ _ _ _ _) =
174184
freeVariables assumedTrue
175185
<> foldMap freeVariables definedTerms
176186
where
177-
SideCondition{assumedTrue, definedTerms} = sideCondition
187+
SideCondition
188+
{ assumedTrue
189+
, definedTerms
190+
} = sideCondition
178191

179192
instance InternalVariable variable => Pretty (SideCondition variable) where
180193
pretty
@@ -208,7 +221,7 @@ instance InternalVariable variable => Pretty (SideCondition variable) where
208221
]
209222

210223
instance From (SideCondition variable) (MultiAnd (Predicate variable)) where
211-
from condition@(SideCondition _ _ _ _) = assumedTrue condition
224+
from condition@(SideCondition _ _ _ _ _) = assumedTrue condition
212225
{-# INLINE from #-}
213226

214227
instance
@@ -234,9 +247,10 @@ assumeTrue ::
234247
assumeTrue assumedTrue =
235248
SideCondition
236249
{ assumedTrue
237-
, definedTerms = HashSet.empty
238250
, replacementsTermLike = HashMap.empty
239251
, replacementsPredicate = HashMap.empty
252+
, definedTerms = HashSet.empty
253+
, simplifiedFunctions = HashSet.empty
240254
}
241255

242256
{- | Assumes a single 'Predicate' to be true in the context of another
@@ -272,25 +286,30 @@ from the combined predicate.
272286
-}
273287
addConditionWithReplacements ::
274288
InternalVariable variable =>
275-
SideCondition variable ->
276289
Condition variable ->
290+
SideCondition variable ->
277291
SideCondition variable
278292
addConditionWithReplacements
279-
sideCondition
280-
(from @(Condition _) @(MultiAnd _) -> newCondition) =
293+
(from @(Condition _) @(MultiAnd _) -> newCondition)
294+
sideCondition =
281295
let combinedConditions = oldCondition <> newCondition
282296
(assumedTrue, assumptions) =
283297
simplifyConjunctionByAssumption combinedConditions
284298
& extract
285299
Assumptions replacementsTermLike replacementsPredicate = assumptions
286300
in SideCondition
287301
{ assumedTrue
288-
, definedTerms
289302
, replacementsTermLike
290303
, replacementsPredicate
304+
, definedTerms
305+
, simplifiedFunctions
291306
}
292307
where
293-
SideCondition{assumedTrue = oldCondition, definedTerms} = sideCondition
308+
SideCondition
309+
{ assumedTrue = oldCondition
310+
, definedTerms
311+
, simplifiedFunctions
312+
} = sideCondition
294313

295314
{- | Smart constructor for creating a 'SideCondition' by just constructing
296315
the replacement table from a conjunction of predicates.
@@ -310,6 +329,7 @@ constructReplacements predicates =
310329
, replacementsTermLike
311330
, replacementsPredicate
312331
, definedTerms = HashSet.empty
332+
, simplifiedFunctions = HashSet.empty
313333
}
314334

315335
{- | Smart constructor for creating a `SideCondition` by assuming
@@ -338,9 +358,10 @@ top :: InternalVariable variable => SideCondition variable
338358
top =
339359
SideCondition
340360
{ assumedTrue = MultiAnd.top
341-
, definedTerms = mempty
342361
, replacementsTermLike = mempty
343362
, replacementsPredicate = mempty
363+
, definedTerms = mempty
364+
, simplifiedFunctions = mempty
344365
}
345366

346367
-- TODO(ana.pantilie): Should we look into removing this?
@@ -353,7 +374,7 @@ toPredicate ::
353374
InternalVariable variable =>
354375
SideCondition variable ->
355376
Predicate variable
356-
toPredicate condition@(SideCondition _ _ _ _) =
377+
toPredicate condition@(SideCondition _ _ _ _ _) =
357378
Predicate.makeAndPredicate
358379
assumedTruePredicate
359380
definedPredicate
@@ -372,7 +393,7 @@ mapVariables ::
372393
AdjSomeVariableName (variable1 -> variable2) ->
373394
SideCondition variable1 ->
374395
SideCondition variable2
375-
mapVariables adj condition@(SideCondition _ _ _ _) =
396+
mapVariables adj condition@(SideCondition _ _ _ _ _) =
376397
let assumedTrue' =
377398
MultiAnd.map (Predicate.mapVariables adj) assumedTrue
378399
replacementsTermLike' =
@@ -381,18 +402,22 @@ mapVariables adj condition@(SideCondition _ _ _ _) =
381402
mapKeysAndValues (Predicate.mapVariables adj) replacementsPredicate
382403
definedTerms' =
383404
HashSet.map (TermLike.mapVariables adj) definedTerms
405+
simplifiedFunctions' =
406+
(HashSet.map . fmap) (TermLike.mapVariables adj) simplifiedFunctions
384407
in SideCondition
385408
{ assumedTrue = assumedTrue'
386409
, replacementsTermLike = replacementsTermLike'
387410
, replacementsPredicate = replacementsPredicate'
388411
, definedTerms = definedTerms'
412+
, simplifiedFunctions = simplifiedFunctions'
389413
}
390414
where
391415
SideCondition
392416
{ assumedTrue
393-
, definedTerms
394417
, replacementsTermLike
395418
, replacementsPredicate
419+
, definedTerms
420+
, simplifiedFunctions
396421
} = condition
397422

398423
-- | Utility function for mapping on the keys and values of a 'HashMap'.
@@ -414,11 +439,18 @@ fromDefinedTerms ::
414439
fromDefinedTerms definedTerms =
415440
top{definedTerms}
416441

442+
{- | Prepares the 'SideCondition' for storing in the term attributes.
443+
Any metadata information used only in particular places during execution
444+
is erased.
445+
-}
417446
toRepresentation ::
418447
InternalVariable variable =>
419448
SideCondition variable ->
420449
SideCondition.Representation
421-
toRepresentation = mkRepresentation
450+
toRepresentation sideCondition =
451+
let sideCondition' =
452+
sideCondition{simplifiedFunctions = HashSet.empty}
453+
in mkRepresentation sideCondition'
422454

423455
-- | Looks up the term in the table of replacements.
424456
replaceTerm ::
@@ -908,3 +940,114 @@ generateNormalizedAcs internalAc =
908940
isDefinedInternal :: TermLike variable -> Bool
909941
isDefinedInternal =
910942
Attribute.isDefined . TermLike.termDefined . TermLike.extractAttributes
943+
944+
fromSimplifiedFunctions ::
945+
InternalVariable variable =>
946+
HashSet (Application Symbol (TermLike variable)) ->
947+
SideCondition variable
948+
fromSimplifiedFunctions simplifiedFunctions =
949+
top{simplifiedFunctions}
950+
951+
{- | Stores all non-constructor function symbols appearing in a term.
952+
Inside a rewrite step, this information is used to avoid trying to
953+
reevaluate functions which could not be evaluated during the 'Simplify'
954+
stage of execution.
955+
956+
See 'isSimplifiedFunction'.
957+
-}
958+
cacheSimplifiedFunctions ::
959+
forall variable.
960+
InternalVariable variable =>
961+
TermLike variable ->
962+
SideCondition variable
963+
cacheSimplifiedFunctions =
964+
fromSimplifiedFunctions
965+
. extractSimplifiedFunctions
966+
where
967+
extractSimplifiedFunctions ::
968+
TermLike variable ->
969+
HashSet (Application Symbol (TermLike variable))
970+
extractSimplifiedFunctions (Recursive.project -> _ :< termF) =
971+
case termF of
972+
TermLike.ApplySymbolF symbolApp ->
973+
let symbol = TermLike.applicationSymbolOrAlias symbolApp
974+
children = TermLike.applicationChildren symbolApp
975+
childrenSet = foldMap extractSimplifiedFunctions children
976+
in if isFunction symbol && not (isConstructor symbol)
977+
then HashSet.singleton symbolApp <> childrenSet
978+
else childrenSet
979+
TermLike.AndF and' ->
980+
foldMap extractSimplifiedFunctions and'
981+
TermLike.ApplyAliasF aliasApp ->
982+
foldMap extractSimplifiedFunctions aliasApp
983+
TermLike.BottomF bottom ->
984+
foldMap extractSimplifiedFunctions bottom
985+
TermLike.CeilF ceil ->
986+
foldMap extractSimplifiedFunctions ceil
987+
TermLike.DomainValueF dv ->
988+
foldMap extractSimplifiedFunctions dv
989+
TermLike.EqualsF equals ->
990+
foldMap extractSimplifiedFunctions equals
991+
TermLike.ExistsF exists ->
992+
foldMap extractSimplifiedFunctions exists
993+
TermLike.FloorF floor' ->
994+
foldMap extractSimplifiedFunctions floor'
995+
TermLike.ForallF forall' ->
996+
foldMap extractSimplifiedFunctions forall'
997+
TermLike.IffF iff ->
998+
foldMap extractSimplifiedFunctions iff
999+
TermLike.ImpliesF implies ->
1000+
foldMap extractSimplifiedFunctions implies
1001+
TermLike.InF in' ->
1002+
foldMap extractSimplifiedFunctions in'
1003+
TermLike.MuF mu ->
1004+
foldMap extractSimplifiedFunctions mu
1005+
TermLike.NextF next ->
1006+
foldMap extractSimplifiedFunctions next
1007+
TermLike.NotF not' ->
1008+
foldMap extractSimplifiedFunctions not'
1009+
TermLike.NuF nu ->
1010+
foldMap extractSimplifiedFunctions nu
1011+
TermLike.OrF or' ->
1012+
foldMap extractSimplifiedFunctions or'
1013+
TermLike.RewritesF rewrites ->
1014+
foldMap extractSimplifiedFunctions rewrites
1015+
TermLike.TopF top' ->
1016+
foldMap extractSimplifiedFunctions top'
1017+
TermLike.InhabitantF inh ->
1018+
foldMap extractSimplifiedFunctions inh
1019+
TermLike.StringLiteralF stringLit ->
1020+
foldMap extractSimplifiedFunctions stringLit
1021+
TermLike.InternalBoolF bool ->
1022+
foldMap extractSimplifiedFunctions bool
1023+
TermLike.InternalBytesF bytes ->
1024+
foldMap extractSimplifiedFunctions bytes
1025+
TermLike.InternalIntF int ->
1026+
foldMap extractSimplifiedFunctions int
1027+
TermLike.InternalStringF string ->
1028+
foldMap extractSimplifiedFunctions string
1029+
TermLike.InternalListF list ->
1030+
foldMap extractSimplifiedFunctions list
1031+
TermLike.InternalMapF map' ->
1032+
foldMap extractSimplifiedFunctions map'
1033+
TermLike.InternalSetF set ->
1034+
foldMap extractSimplifiedFunctions set
1035+
TermLike.VariableF var ->
1036+
foldMap extractSimplifiedFunctions var
1037+
TermLike.EndiannessF end ->
1038+
foldMap extractSimplifiedFunctions end
1039+
TermLike.SignednessF sign ->
1040+
foldMap extractSimplifiedFunctions sign
1041+
TermLike.InjF inj ->
1042+
foldMap extractSimplifiedFunctions inj
1043+
1044+
{- | Decides whether a function can be further simplified or not.
1045+
See also 'cacheSimplifiedFunctions'.
1046+
-}
1047+
isSimplifiedFunction ::
1048+
InternalVariable variable =>
1049+
Application Symbol (TermLike variable) ->
1050+
SideCondition variable ->
1051+
Bool
1052+
isSimplifiedFunction app SideCondition{simplifiedFunctions} =
1053+
HashSet.member app simplifiedFunctions

0 commit comments

Comments
 (0)