@@ -178,7 +178,6 @@ mergeDefs k1 k2
178178 <$> mergeDisjoint Def. modules k1 k2
179179 <*> mergeDisjoint Def. sorts k1 k2
180180 <*> mergeDisjoint Def. symbols k1 k2
181- <*> mergeDisjoint Def. aliases k1 k2
182181 <*> pure (mergeTheories rewriteTheory k1 k2)
183182 <*> pure (mergeTheories functionEquations k1 k2)
184183 <*> pure (mergeTheories simplifications k1 k2)
@@ -223,7 +222,6 @@ addModule
223222 { name = Syntax. Id n
224223 , sorts = parsedSorts
225224 , symbols = parsedSymbols
226- , aliases = parsedAliases
227225 , axioms = parsedAxioms
228226 }
229227 ( Imported
@@ -232,7 +230,6 @@ addModule
232230 , modules = currentModules
233231 , sorts = currentSorts
234232 , symbols = currentSymbols
235- , aliases = currentAliases
236233 , rewriteTheory = currentRewriteTheory
237234 , functionEquations = currentFctEqs
238235 , simplifications = currentSimpls
@@ -286,76 +283,20 @@ addModule
286283 let symbols =
287284 renameSmtLibDuplicates symbols'
288285
289- let defWithNewSortsAndSymbols =
286+ let def =
290287 Partial
291288 KoreDefinition
292289 { attributes = defAttributes
293290 , modules
294291 , sorts = sorts' -- no subsort information yet
295292 , symbols
296- , aliases = currentAliases -- no aliases yet
297293 , rewriteTheory = currentRewriteTheory -- no rules yet
298294 , functionEquations = Map. empty
299295 , simplifications = Map. empty
300296 , ceils = Map. empty
301297 }
302298
303- let internaliseAlias ::
304- ParsedAlias ->
305- Except DefinitionError (Def. AliasName , Alias )
306- -- TODO(Ana): do we need to handle attributes?
307- internaliseAlias palias@ ParsedAlias {name, sortVars, argSorts, sort, args, rhs} = do
308- unless
309- (length argSorts == length args)
310- (throwE (DefinitionAliasError name. getId . WrongAliasSortCount $ palias))
311- let paramNames = (. getId) <$> sortVars
312- params = Def. SortVar . textToBS <$> paramNames
313- argNames = textToBS . (. getId) <$> args
314- internalName = textToBS name. getId
315- internalArgSorts <-
316- traverse
317- (withExcept DefinitionSortError . internaliseSort (Set. fromList paramNames) sorts')
318- argSorts
319- internalResSort <-
320- withExcept DefinitionSortError $
321- internaliseSort (Set. fromList paramNames) sorts' sort
322- let internalArgs = uncurry Def. Variable <$> zip internalArgSorts argNames
323-
324- (rhsTerm, predicates, ceilConditions, substitution, _unsupported) <- -- FIXME
325- withExcept (DefinitionAliasError name. getId . InconsistentAliasPattern . (: [] )) $
326- internalisePattern
327- AllowAlias
328- IgnoreSubsorts
329- (Just sortVars)
330- defWithNewSortsAndSymbols. partial
331- rhs
332- unless (null substitution) $
333- throwE $
334- DefinitionAliasError name. getId $
335- InconsistentAliasPattern [SubstitutionNotAllowed ]
336- unless (null predicates) $
337- throwE $
338- DefinitionAliasError name. getId $
339- InconsistentAliasPattern [PredicateNotAllowed ]
340- unless (null ceilConditions) $
341- throwE $
342- DefinitionAliasError name. getId $
343- InconsistentAliasPattern [CeilNotAllowed ]
344- let rhsSort = Util. sortOfTerm rhsTerm
345- unless
346- (rhsSort == internalResSort)
347- (throwE (DefinitionSortError (GeneralError " IncompatibleSorts" )))
348- return (internalName, Alias {name = internalName, params, args = internalArgs, rhs = rhsTerm})
349- -- filter out "antiLeft" aliases, recognised by name and argument count
350- notPriority :: ParsedAlias -> Bool
351- notPriority alias =
352- not $ null alias. args && " priority" `Text.isPrefixOf` alias. name. getId
353- newAliases <- traverse internaliseAlias $ filter notPriority parsedAliases
354- let aliases = Map. fromList newAliases <> currentAliases
355-
356- let defWithAliases :: PartialDefinition
357- defWithAliases = Partial defWithNewSortsAndSymbols. partial{aliases}
358- newAxioms <- mapMaybeM (internaliseAxiom defWithAliases) parsedAxioms
299+ newAxioms <- mapMaybeM (internaliseAxiom def) parsedAxioms
359300
360301 let newRewriteRules = mapMaybe retractRewriteRule newAxioms
361302 subsortPairs = mapMaybe retractSubsortRule newAxioms
@@ -378,7 +319,7 @@ addModule
378319 subsortClosure sorts' subsortPairs
379320
380321 pure $
381- defWithAliases . partial
322+ def . partial
382323 { sorts
383324 , rewriteTheory
384325 , functionEquations
@@ -790,16 +731,12 @@ internaliseAxiom (Partial partialDefinition) parsedAxiom =
790731 lhs
791732 rhs
792733 attribs
793- RewriteRuleAxiom' alias args rhs' attribs ->
794- let (rhs, existentials) = extractExistentials rhs'
795- in Just . RewriteRuleAxiom
796- <$> internaliseRewriteRule
797- partialDefinition
798- existentials
799- (textToBS alias)
800- args
801- rhs
802- attribs
734+ RewriteRuleAxiom' {} ->
735+ throwE $
736+ DefinitionSortError $
737+ GeneralError
738+ ( " Rules with antiLeft aliases are no longer supported. Please rekompile your definition with a newer version of K."
739+ )
803740 SimplificationAxiom' requires lhs rhs sortVars attribs ->
804741 Just
805742 <$> internaliseSimpleEquation
@@ -828,9 +765,6 @@ internaliseAxiom (Partial partialDefinition) parsedAxiom =
828765 sortVars
829766 attribs
830767
831- orFailWith :: Maybe a -> e -> Except e a
832- mbX `orFailWith` err = maybe (throwE err) pure mbX
833-
834768internalisePatternEnsureNoSubstitutionOrCeilOrUnsupported ::
835769 KoreDefinition ->
836770 SourceRef ->
@@ -913,85 +847,6 @@ internaliseRewriteRuleNoAlias partialDefinition exs left right axAttributes = do
913847 let variableName = textToBS name. getId
914848 pure $ Variable {variableSort, variableName}
915849
916- internaliseRewriteRule ::
917- KoreDefinition ->
918- [(Id , Sort )] ->
919- AliasName ->
920- [Syntax. KorePattern ] ->
921- Syntax. KorePattern ->
922- AxiomAttributes ->
923- Except DefinitionError (RewriteRule k )
924- internaliseRewriteRule partialDefinition exs aliasName aliasArgs right axAttributes = do
925- let ref = sourceRef axAttributes
926- alias <-
927- withExcept (DefinitionAliasError $ Text. decodeLatin1 aliasName) $
928- Map. lookup aliasName partialDefinition. aliases
929- `orFailWith` UnknownAlias aliasName
930- args <-
931- traverse
932- ( withExcept (DefinitionPatternError ref)
933- . internaliseTerm AllowAlias IgnoreSubsorts Nothing partialDefinition
934- )
935- aliasArgs
936- -- prefix all variables in lhs and rhs with "Rule#" and "Ex#" to avoid
937- -- name clashes with patterns from the user
938- lhs <- Util. modifyVariablesInT (Util. modifyVarName Util. markAsRuleVar) <$> expandAlias alias args
939-
940- existentials' <- fmap Set. fromList $ withExcept (DefinitionPatternError ref) $ mapM mkVar exs
941- let renameVariable v
942- | v `Set.member` existentials' = Util. modifyVarName Util. markAsExVar v
943- | otherwise = Util. modifyVarName Util. markAsRuleVar v
944- (rhs, ensures) <-
945- internalisePatternEnsureNoSubstitutionOrCeilOrUnsupported
946- partialDefinition
947- ref
948- Nothing
949- renameVariable
950- right
951-
952- let notPreservesDefinednessReasons =
953- -- users can override the definedness computation by an explicit attribute
954- if coerce axAttributes. preserving
955- then []
956- else
957- [ UndefinedSymbol s. name
958- | s <- Util. filterTermSymbols (not . Util. isDefinedSymbol) rhs
959- ]
960- containsAcSymbols =
961- Util. checkTermSymbols Util. checkSymbolIsAc lhs
962- computedAttributes =
963- ComputedAxiomAttributes {notPreservesDefinednessReasons, containsAcSymbols}
964- existentials = Set. map (Util. modifyVarName Util. markAsExVar) existentials'
965- attributes =
966- axAttributes
967- { concreteness = Util. modifyVarNameConcreteness Util. markAsRuleVar axAttributes. concreteness
968- }
969- return
970- RewriteRule
971- { lhs
972- , rhs
973- , requires = mempty
974- , ensures
975- , attributes
976- , computedAttributes
977- , existentials
978- }
979- where
980- mkVar (name, sort) = do
981- variableSort <- lookupInternalSort Nothing partialDefinition. sorts right sort
982- let variableName = textToBS name. getId
983- pure $ Variable {variableSort, variableName}
984-
985- expandAlias :: Alias -> [Def. Term ] -> Except DefinitionError Def. Term
986- expandAlias alias currentArgs
987- | length alias. args /= length currentArgs =
988- throwE $
989- DefinitionAliasError (Text. decodeLatin1 alias. name) $
990- WrongAliasArgCount alias currentArgs
991- | otherwise = do
992- let substitution = Map. fromList (zip alias. args currentArgs)
993- pure $ Util. substituteInTerm substitution alias. rhs
994-
995850{- | Internalises simplification rules, for term simplification
996851 (represented as a 'RewriteRule').
997852
@@ -1320,7 +1175,6 @@ data DefinitionError
13201175 | DefinitionAttributeError Text
13211176 | DefinitionSortError SortError
13221177 | DefinitionPatternError SourceRef PatternError
1323- | DefinitionAliasError Text AliasError
13241178 | DefinitionAxiomError AxiomError
13251179 | DefinitionTermOrPredicateError SourceRef TermOrPredicateError
13261180 | ElemSymbolMalformed Def. Symbol
@@ -1349,9 +1203,6 @@ instance FromModifiersT mods => Pretty (PrettyWithModifiers mods DefinitionError
13491203 pretty $ " Sort error: " <> renderSortError @ mods (PrettyWithModifiers sortErr)
13501204 DefinitionPatternError ref patErr ->
13511205 " Pattern error in " <> pretty ref <> " : " <> pretty (show patErr)
1352- -- TODO define a pretty instance?
1353- DefinitionAliasError name err ->
1354- pretty $ " Alias error in " <> Text. unpack name <> " : " <> show err
13551206 DefinitionAxiomError err ->
13561207 " Bad rewrite rule " <> pretty err
13571208 DefinitionTermOrPredicateError ref (PatternExpected p) ->
@@ -1398,13 +1249,6 @@ definitionErrorToRpcError = \case
13981249 either (const " unknown location" ) pretty $
13991250 runExcept (Attributes. readLocation rule. attributes)
14001251
1401- data AliasError
1402- = UnknownAlias AliasName
1403- | WrongAliasSortCount ParsedAlias
1404- | WrongAliasArgCount Alias [Def. Term ]
1405- | InconsistentAliasPattern [PatternError ]
1406- deriving stock (Eq , Show )
1407-
14081252data AxiomError
14091253 = MalformedRewriteRule ParsedAxiom
14101254 | MalformedEquation ParsedAxiom
0 commit comments