Skip to content

Commit

Permalink
Consolidate variable marking API (#461)
Browse files Browse the repository at this point in the history
Closes #456

---------

Co-authored-by: rv-jenkins <[email protected]>
  • Loading branch information
geo2a and rv-jenkins authored Jan 16, 2024
1 parent 98e9b26 commit 2d2dd7f
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 21 deletions.
2 changes: 1 addition & 1 deletion library/Booster/Pattern/Rewrite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -328,7 +328,7 @@ applyRule pat@Pattern{ceilConditions} rule = runRewriteRuleAppT $ do
forbiddenVars = varsFromInput <> varsFromSubst
existentialSubst =
Map.fromSet
(\v -> Var $ freshenVar v{variableName = stripVarOriginPrefix v.variableName} forbiddenVars)
(\v -> Var $ freshenVar v{variableName = stripMarker v.variableName} forbiddenVars)
rule.existentials

-- modify the substitution to include the existentials
Expand Down
18 changes: 13 additions & 5 deletions library/Booster/Pattern/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,9 @@ module Booster.Pattern.Util (
abstractSymbolicConstructorArguments,
cellSymbolStats,
cellVariableStats,
stripVarOriginPrefix,
stripMarker,
markAsExVar,
markAsRuleVar,
incrementNameCounter,
) where

Expand Down Expand Up @@ -117,11 +119,17 @@ modifyVariablesInT f = cata $ \case
modifyVarName :: (VarName -> VarName) -> Variable -> Variable
modifyVarName f v = v{variableName = f v.variableName}

{- | Strip variable provenance prefixes introduced
in "Syntax.ParsedKore.Internalize.internationalization"
markAsRuleVar :: VarName -> VarName
markAsRuleVar = ("Rule#" <>)

markAsExVar :: VarName -> VarName
markAsExVar = ("Ex#" <>)

{- | Strip variable provenance prefixes introduced using "markAsRuleVar" and "markAsExVar"
in "Syntax.ParsedKore.Internalize"
-}
stripVarOriginPrefix :: VarName -> VarName
stripVarOriginPrefix name =
stripMarker :: VarName -> VarName
stripMarker name =
let noRule = BS.stripPrefix "Rule#" name
noEx = BS.stripPrefix "Ex#" name
in fromMaybe name $ noRule <|> noEx
Expand Down
29 changes: 14 additions & 15 deletions library/Booster/Syntax/ParsedKore/Internalise.hs
Original file line number Diff line number Diff line change
Expand Up @@ -786,14 +786,15 @@ internaliseRewriteRuleNoAlias ::
Except DefinitionError (RewriteRule k)
internaliseRewriteRuleNoAlias partialDefinition exs left right axAttributes = do
let ref = sourceRef axAttributes
-- prefix all variables in lhs and rhs with "Rule#" and "Ex#" to avoid
-- name clashes with patterns from the user
-- mark all variables in lhs as rule-variables
-- and in rhs as either rule- or existential-variables
-- to avoid name clashes with patterns from the user;
-- filter out literal `Top` constraints
lhs <- internalisePattern' ref (Util.modifyVarName ("Rule#" <>)) left
lhs <- internalisePattern' ref (Util.modifyVarName Util.markAsRuleVar) left
existentials' <- fmap Set.fromList $ withExcept (DefinitionPatternError ref) $ mapM mkVar exs
let renameVariable v
| v `Set.member` existentials' = Util.modifyVarName ("Ex#" <>) v
| otherwise = Util.modifyVarName ("Rule#" <>) v
| v `Set.member` existentials' = Util.modifyVarName Util.markAsExVar v
| otherwise = Util.modifyVarName Util.markAsRuleVar v
rhs <- internalisePattern' ref renameVariable right
let notPreservesDefinednessReasons =
-- users can override the definedness computation by an explicit attribute
Expand All @@ -803,15 +804,11 @@ internaliseRewriteRuleNoAlias partialDefinition exs left right axAttributes = do
[ UndefinedSymbol s.name
| s <- Util.filterTermSymbols (not . Util.isDefinedSymbol) rhs.term
]
-- <> [ UndefinedSymbol s.name
-- | c <- Set.toList lhs.constraints
-- , s <- Util.filterTermSymbols (not . Util.isDefinedSymbol) $ coerce c
-- ]
containsAcSymbols =
Util.checkTermSymbols Util.checkSymbolIsAc lhs.term
computedAttributes =
ComputedAxiomAttributes{notPreservesDefinednessReasons, containsAcSymbols}
existentials = Set.map (Util.modifyVarName ("Ex#" <>)) existentials'
existentials = Set.map (Util.modifyVarName Util.markAsExVar) existentials'
return
RewriteRule
{ lhs = lhs.term
Expand Down Expand Up @@ -866,13 +863,13 @@ internaliseRewriteRule partialDefinition exs aliasName aliasArgs right axAttribu
-- name clashes with patterns from the user
-- filter out literal `Top` constraints
lhs <-
fmap (removeTrueBools . Util.modifyVariables (Util.modifyVarName ("Rule#" <>))) $
fmap (removeTrueBools . Util.modifyVariables (Util.modifyVarName Util.markAsRuleVar)) $
retractPattern result
`orFailWith` DefinitionTermOrPredicateError ref (PatternExpected result)
existentials' <- fmap Set.fromList $ withExcept (DefinitionPatternError ref) $ mapM mkVar exs
let renameVariable v
| v `Set.member` existentials' = Util.modifyVarName ("Ex#" <>) v
| otherwise = Util.modifyVarName ("Rule#" <>) v
| v `Set.member` existentials' = Util.modifyVarName Util.markAsExVar v
| otherwise = Util.modifyVarName Util.markAsRuleVar v
rhs <- internalisePattern' ref renameVariable right

let notPreservesDefinednessReasons =
Expand All @@ -887,9 +884,11 @@ internaliseRewriteRule partialDefinition exs aliasName aliasArgs right axAttribu
Util.checkTermSymbols Util.checkSymbolIsAc lhs.term
computedAttributes =
ComputedAxiomAttributes{notPreservesDefinednessReasons, containsAcSymbols}
existentials = Set.map (Util.modifyVarName ("Ex#" <>)) existentials'
existentials = Set.map (Util.modifyVarName Util.markAsExVar) existentials'
attributes =
axAttributes{concreteness = Util.modifyVarNameConcreteness ("Rule#" <>) axAttributes.concreteness}
axAttributes
{ concreteness = Util.modifyVarNameConcreteness Util.markAsRuleVar axAttributes.concreteness
}
return
RewriteRule
{ lhs = lhs.term
Expand Down

0 comments on commit 2d2dd7f

Please sign in to comment.