@@ -10,7 +10,6 @@ module Kore.Equation.Equation (
1010 refreshVariables ,
1111 isSimplificationRule ,
1212 equationPriority ,
13- substitute ,
1413 identifiers ,
1514) where
1615
@@ -49,12 +48,14 @@ import Kore.Internal.Symbol (
4948import Kore.Internal.TermLike (
5049 InternalVariable ,
5150 TermLike ,
51+ mkVar ,
5252 )
5353import qualified Kore.Internal.TermLike as TermLike
5454import Kore.Sort
5555import Kore.Step.Step (
5656 Renaming ,
5757 )
58+ import Kore.Substitute
5859import Kore.Syntax.Application (
5960 Application (.. ),
6061 )
@@ -142,6 +143,25 @@ instance SQL.Column (Equation VariableName) where
142143 defineColumn = SQL. defineForeignKeyColumn
143144 toColumn = SQL. toForeignKeyColumn
144145
146+ instance InternalVariable variable => Substitute (Equation variable ) where
147+ type TermType (Equation variable ) = TermLike variable
148+
149+ type VariableNameType (Equation variable ) = variable
150+
151+ substitute assignments equation =
152+ Equation
153+ { requires = substitute assignments (requires equation)
154+ , argument = substitute assignments <$> argument equation
155+ , antiLeft = substitute assignments <$> antiLeft equation
156+ , left = substitute assignments (left equation)
157+ , right = substitute assignments (right equation)
158+ , ensures = substitute assignments (ensures equation)
159+ , attributes = attributes equation
160+ }
161+
162+ rename = substitute . fmap mkVar
163+ {-# INLINE rename #-}
164+
145165toTermLike ::
146166 InternalVariable variable =>
147167 Sort ->
@@ -261,8 +281,8 @@ refreshVariables ::
261281refreshVariables
262282 (FreeVariables. toNames -> avoid)
263283 equation@ (Equation _ _ _ _ _ _ _) =
264- let rename :: Map (SomeVariableName variable ) (SomeVariable variable )
265- rename =
284+ let rename' :: Map (SomeVariableName variable ) (SomeVariable variable )
285+ rename' =
266286 FreeVariables. toSet originalFreeVariables
267287 & Fresh. refreshVariables avoid
268288 lookupSomeVariableName ::
@@ -273,7 +293,7 @@ refreshVariables
273293 lookupSomeVariableName variable =
274294 do
275295 let injected = inject @ (SomeVariableName _ ) variable
276- someVariableName <- variableName <$> Map. lookup injected rename
296+ someVariableName <- variableName <$> Map. lookup injected rename'
277297 retract someVariableName
278298 & fromMaybe variable
279299 adj :: AdjSomeVariableName (variable -> variable )
@@ -295,12 +315,12 @@ refreshVariables
295315 ( variableName variable
296316 , TermLike. mkVar (mapSomeVariable adj variable)
297317 )
298- left' = TermLike. substitute subst left
299- requires' = Predicate. substitute subst requires
300- argument' = Predicate. substitute subst <$> argument
301- antiLeft' = Predicate. substitute subst <$> antiLeft
302- right' = TermLike. substitute subst right
303- ensures' = Predicate. substitute subst ensures
318+ left' = substitute subst left
319+ requires' = substitute subst requires
320+ argument' = substitute subst <$> argument
321+ antiLeft' = substitute subst <$> antiLeft
322+ right' = substitute subst right
323+ ensures' = substitute subst ensures
304324 attributes' = Attribute. mapAxiomVariables adj attributes
305325 equation' =
306326 equation
@@ -312,7 +332,7 @@ refreshVariables
312332 , ensures = ensures'
313333 , attributes = attributes'
314334 }
315- in (rename, equation')
335+ in (rename' , equation')
316336 where
317337 Equation
318338 { requires
@@ -334,32 +354,6 @@ isSimplificationRule Equation{attributes} =
334354equationPriority :: Equation variable -> Integer
335355equationPriority = Attribute. getPriorityOfAxiom . attributes
336356
337- substitute ::
338- InternalVariable variable =>
339- Map (SomeVariableName variable ) (TermLike variable ) ->
340- Equation variable ->
341- Equation variable
342- substitute assignments equation =
343- Equation
344- { requires = Predicate. substitute assignments requires
345- , argument = Predicate. substitute assignments <$> argument
346- , antiLeft = Predicate. substitute assignments <$> antiLeft
347- , left = TermLike. substitute assignments left
348- , right = TermLike. substitute assignments right
349- , ensures = Predicate. substitute assignments ensures
350- , attributes
351- }
352- where
353- Equation
354- { requires
355- , argument
356- , antiLeft
357- , left
358- , right
359- , ensures
360- , attributes
361- } = equation
362-
363357{- | The list of identifiers for an 'Equation'.
364358
365359The identifiers are:
0 commit comments