@@ -4,6 +4,7 @@ License : NCSA
4
4
5
5
-}
6
6
7
+ {-# LANGUAGE Strict #-}
7
8
module Kore.Equation.Application
8
9
( attemptEquation
9
10
, AttemptEquationResult
@@ -113,10 +114,6 @@ import Kore.TopBottom
113
114
import Kore.Unparser
114
115
( Unparse (.. )
115
116
)
116
- import Kore.Variables.Target
117
- ( Target
118
- )
119
- import qualified Kore.Variables.Target as Target
120
117
import Log
121
118
( Entry (.. )
122
119
, MonadLog
@@ -155,7 +152,7 @@ attemptEquation
155
152
=> MonadSimplify simplifier
156
153
=> InternalVariable variable
157
154
=> SideCondition variable
158
- -> TermLike ( Target variable )
155
+ -> TermLike variable
159
156
-> Equation variable
160
157
-> simplifier (AttemptEquationResult variable )
161
158
attemptEquation sideCondition termLike equation =
@@ -179,20 +176,16 @@ attemptEquation sideCondition termLike equation =
179
176
& whileMatch
180
177
(equation', predicate) <-
181
178
applyAndSelectMatchResult matchResults
182
- let matchPredicate' =
183
- Predicate. mapVariables
184
- (pure Target. unTarget)
185
- matchPredicate
186
179
return
187
180
( equation'
188
- , makeAndPredicate predicate matchPredicate'
181
+ , makeAndPredicate predicate matchPredicate
189
182
)
190
183
let Equation { requires } = equation'
191
184
checkRequires sideCondition predicate requires & whileCheckRequires
192
185
let Equation { right, ensures } = equation'
193
186
return $ Pattern. withCondition right $ from @ (Predicate _ ) ensures
194
187
where
195
- equationRenamed = targetEquationVariables sideCondition termLike equation
188
+ equationRenamed = refreshVariables sideCondition termLike equation
196
189
matchError =
197
190
MatchError
198
191
{ matchTerm = termLike
@@ -203,7 +196,7 @@ attemptEquation sideCondition termLike equation =
203
196
& MaybeT & noteT matchError
204
197
205
198
applyAndSelectMatchResult
206
- :: [MatchResult ( Target variable ) ]
199
+ :: [MatchResult variable ]
207
200
-> ExceptT
208
201
(AttemptEquationError variable )
209
202
simplifier
@@ -234,13 +227,13 @@ applySubstitutionAndSimplify
234
227
:: HasCallStack
235
228
=> MonadSimplify simplifier
236
229
=> InternalVariable variable
237
- => Predicate ( Target variable )
238
- -> Maybe (Predicate ( Target variable ) )
239
- -> Map (SomeVariableName ( Target variable )) (TermLike ( Target variable ) )
230
+ => Predicate variable
231
+ -> Maybe (Predicate variable )
232
+ -> Map (SomeVariableName variable ) (TermLike variable )
240
233
-> ExceptT
241
- (MatchError ( Target variable ) )
234
+ (MatchError variable )
242
235
simplifier
243
- [MatchResult ( Target variable ) ]
236
+ [MatchResult variable ]
244
237
applySubstitutionAndSimplify
245
238
argument
246
239
antiLeft
@@ -284,9 +277,9 @@ applyMatchResult
284
277
:: forall monad variable
285
278
. Monad monad
286
279
=> InternalVariable variable
287
- => Equation ( Target variable )
288
- -> MatchResult ( Target variable )
289
- -> ExceptT (ApplyMatchResultErrors ( Target variable ) ) monad
280
+ => Equation variable
281
+ -> MatchResult variable
282
+ -> ExceptT (ApplyMatchResultErrors variable ) monad
290
283
(Equation variable , Predicate variable )
291
284
applyMatchResult equation matchResult@ (predicate, substitution) = do
292
285
case errors of
@@ -297,21 +290,28 @@ applyMatchResult equation matchResult@(predicate, substitution) = do
297
290
}
298
291
_ -> return ()
299
292
let predicate' =
300
- Predicate. substitute substitution predicate
301
- & Predicate. mapVariables (pure Target. unTarget)
293
+ Predicate. substitute orientedSubstitution predicate
302
294
equation' =
303
- Equation. substitute substitution equation
304
- & Equation. mapVariables (pure Target. unTarget)
295
+ Equation. substitute orientedSubstitution equation
305
296
return (equation', predicate')
306
297
where
307
- equationVariables = freeVariables equation & FreeVariables. toList
298
+ orientedSubstitution = Substitution. orientSubstitution occursInEquation substitution
299
+
300
+ equationVariables = freeVariables equation
301
+
302
+ occursInEquation :: (SomeVariableName variable -> Bool )
303
+ occursInEquation = \ someVariableName ->
304
+ Set. member someVariableName equationVariableNames
305
+
306
+ equationVariableNames =
307
+ Set. map variableName (FreeVariables. toSet equationVariables)
308
308
309
309
errors =
310
- concatMap checkVariable equationVariables
311
- <> checkNonTargetVariables
310
+ concatMap checkVariable ( FreeVariables. toList equationVariables)
311
+ <> checkNotInEquation
312
312
313
313
checkVariable Variable { variableName } =
314
- case Map. lookup variableName substitution of
314
+ case Map. lookup variableName orientedSubstitution of
315
315
Nothing -> [NotMatched variableName]
316
316
Just termLike ->
317
317
checkConcreteVariable variableName termLike
@@ -331,9 +331,9 @@ applyMatchResult equation matchResult@(predicate, substitution) = do
331
331
| otherwise
332
332
= empty
333
333
334
- checkNonTargetVariables =
334
+ checkNotInEquation =
335
335
NonMatchingSubstitution
336
- <$> filter Target. isSomeNonTargetName (Map. keys substitution )
336
+ <$> filter ( not . occursInEquation) (Map. keys orientedSubstitution )
337
337
338
338
Equation { attributes } = equation
339
339
concretes =
@@ -400,37 +400,27 @@ checkRequires sideCondition predicate requires =
400
400
. Simplifier. localSimplifierAxioms (const mempty )
401
401
withAxioms = id
402
402
403
- {- | Make the 'Equation' variables distinct from the initial pattern.
404
-
405
- The variables are marked 'Target' and renamed to avoid any variables in the
406
- 'SideCondition' or the 'TermLike'.
407
-
408
- -}
409
- targetEquationVariables
403
+ refreshVariables
410
404
:: forall variable
411
405
. InternalVariable variable
412
406
=> SideCondition variable
413
- -> TermLike ( Target variable )
407
+ -> TermLike variable
414
408
-> Equation variable
415
- -> Equation ( Target variable )
416
- targetEquationVariables sideCondition initial =
409
+ -> Equation variable
410
+ refreshVariables sideCondition initial =
417
411
snd
418
412
. Equation. refreshVariables avoiding
419
- . Equation. mapVariables Target. mkUnifiedTarget
420
413
where
421
414
avoiding = sideConditionVariables <> freeVariables initial
422
- sideConditionVariables =
423
- FreeVariables. mapFreeVariables
424
- Target. mkUnifiedNonTarget
425
- $ freeVariables sideCondition
415
+ sideConditionVariables = freeVariables sideCondition
426
416
427
417
-- * Errors
428
418
429
419
{- | Errors that can occur during 'attemptEquation'.
430
420
-}
431
421
data AttemptEquationError variable
432
- = WhileMatch ! (MatchError ( Target variable ) )
433
- | WhileApplyMatchResult ! (ApplyMatchResultErrors ( Target variable ) )
422
+ = WhileMatch ! (MatchError variable )
423
+ | WhileApplyMatchResult ! (ApplyMatchResultErrors variable )
434
424
| WhileCheckRequires ! (CheckRequiresError variable )
435
425
deriving (Eq , Ord , Show )
436
426
deriving (GHC.Generic )
@@ -445,27 +435,25 @@ mapAttemptEquationErrorVariables
445
435
mapAttemptEquationErrorVariables adj =
446
436
\ case
447
437
WhileMatch matchError ->
448
- WhileMatch $ mapMatchErrorVariables adjTarget matchError
438
+ WhileMatch $ mapMatchErrorVariables adj matchError
449
439
WhileApplyMatchResult applyMatchResultErrors ->
450
440
WhileApplyMatchResult
451
441
$ mapApplyMatchResultErrorsVariables
452
- adjTarget
442
+ adj
453
443
applyMatchResultErrors
454
444
WhileCheckRequires checkRequiresError ->
455
445
WhileCheckRequires
456
446
$ mapCheckRequiresErrorVariables adj checkRequiresError
457
- where
458
- adjTarget = fmap <$> adj
459
447
460
448
whileMatch
461
449
:: Functor monad
462
- => ExceptT (MatchError ( Target variable ) ) monad a
450
+ => ExceptT (MatchError variable ) monad a
463
451
-> ExceptT (AttemptEquationError variable ) monad a
464
452
whileMatch = withExceptT WhileMatch
465
453
466
454
whileApplyMatchResult
467
455
:: Functor monad
468
- => ExceptT (ApplyMatchResultErrors ( Target variable ) ) monad a
456
+ => ExceptT (ApplyMatchResultErrors variable ) monad a
469
457
-> ExceptT (AttemptEquationError variable ) monad a
470
458
whileApplyMatchResult = withExceptT WhileApplyMatchResult
471
459
0 commit comments