Skip to content

Commit 053ed88

Browse files
committed
Add substitution conversion helpers
1 parent 45eddb9 commit 053ed88

File tree

2 files changed

+19
-15
lines changed

2 files changed

+19
-15
lines changed

booster/library/Booster/Pattern/Bool.hs

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,9 @@ module Booster.Pattern.Bool (
1010
negateBool,
1111
splitBoolPredicates,
1212
splitAndBools,
13+
mkEq,
1314
destructEq,
15+
asEquations,
1416
-- patterns
1517
pattern TrueBool,
1618
pattern FalseBool,
@@ -25,6 +27,8 @@ module Booster.Pattern.Bool (
2527
) where
2628

2729
import Data.ByteString.Char8 (ByteString)
30+
import Data.Map.Strict (Map)
31+
import Data.Map.Strict qualified as Map
2832

2933
import Booster.Definition.Attributes.Base (
3034
FunctionType (..),
@@ -52,7 +56,7 @@ import Booster.Pattern.Base (
5256
pattern SymbolApplication,
5357
pattern Var,
5458
)
55-
import Booster.Pattern.Util (isConcrete)
59+
import Booster.Pattern.Util (isConcrete, sortOfTerm)
5660
import Booster.SMT.Base (SExpr (Atom), SMTId (..))
5761

5862
pattern HookedTotalFunction :: ByteString -> SymbolAttributes
@@ -210,6 +214,12 @@ splitAndBools p@(Predicate t)
210214
| AndBool l r <- t = concatMap (splitAndBools . Predicate) [l, r]
211215
| otherwise = [p]
212216

217+
mkEq :: Variable -> Term -> Predicate
218+
mkEq x t = Predicate $ case sortOfTerm t of
219+
SortInt -> EqualsInt (Var x) t
220+
SortBool -> EqualsBool (Var x) t
221+
otherSort -> EqualsK (KSeq otherSort (Var x)) (KSeq otherSort t)
222+
213223
-- | Pattern match on an equality predicate and try extracting a variable assignment
214224
destructEq :: Predicate -> Maybe (Variable, Term)
215225
destructEq = \case
@@ -218,3 +228,7 @@ destructEq = \case
218228
Predicate
219229
(EqualsK (KSeq _lhsSort (Var x)) (KSeq _rhsSort t)) -> Just (x, t)
220230
_ -> Nothing
231+
232+
-- | turns a substitution into a list of equations
233+
asEquations :: Map Variable Term -> [Predicate]
234+
asEquations = map (uncurry mkEq) . Map.assocs

booster/library/Booster/Syntax/Json/Internalise.hs

Lines changed: 4 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -463,7 +463,7 @@ mkSubstitution initialSubst =
463463
Map.partition ((== 1) . length) $
464464
Map.fromListWith (<>) [(v, [t]) | SubstitutionPred v t <- initialSubst]
465465
equations =
466-
[mkEq v t | (v, ts) <- Map.assocs duplicates, t <- ts]
466+
[Internal.mkEq v t | (v, ts) <- Map.assocs duplicates, t <- ts]
467467
in execState breakCycles (Map.map head substMap, equations)
468468
where
469469
breakCycles :: State (Map Internal.Variable Internal.Term, [Internal.Predicate]) ()
@@ -477,20 +477,10 @@ mkSubstitution initialSubst =
477477
else do
478478
modify $ \(m, eqs) ->
479479
( m `Map.withoutKeys` cycleNodes
480-
, eqs <> (map (uncurry mkEq) $ Map.assocs $ m `Map.restrictKeys` cycleNodes)
480+
, eqs <> (map (uncurry Internal.mkEq) $ Map.assocs $ m `Map.restrictKeys` cycleNodes)
481481
)
482482
breakCycles
483483

484-
mkEq :: Internal.Variable -> Internal.Term -> Internal.Predicate
485-
mkEq x t = Internal.Predicate $ case sortOfTerm t of
486-
Internal.SortInt -> Internal.EqualsInt (Internal.Var x) t
487-
Internal.SortBool -> Internal.EqualsBool (Internal.Var x) t
488-
otherSort -> Internal.EqualsK (Internal.KSeq otherSort (Internal.Var x)) (Internal.KSeq otherSort t)
489-
490-
-- | turns a substitution into a list of equations
491-
asEquations :: Map Internal.Variable Internal.Term -> [Internal.Predicate]
492-
asEquations = map (uncurry mkEq) . Map.assocs
493-
494484
internalisePred ::
495485
Flag "alias" ->
496486
Flag "subsorts" ->
@@ -562,12 +552,12 @@ internalisePred allowAlias checkSubsorts sortVars definition@KoreDefinition{sort
562552
pure [BoolPred $ Internal.Predicate $ Internal.NotBool x]
563553
(_, Internal.Var x, t)
564554
| x `Set.member` freeVariables t ->
565-
pure [BoolPred $ mkEq x t]
555+
pure [BoolPred $ Internal.mkEq x t]
566556
| otherwise ->
567557
pure [SubstitutionPred x t]
568558
(_, t, Internal.Var x)
569559
| x `Set.member` freeVariables t ->
570-
pure [BoolPred $ mkEq x t]
560+
pure [BoolPred $ Internal.mkEq x t]
571561
| otherwise ->
572562
pure [SubstitutionPred x t]
573563
(Internal.SortInt, _, _) ->

0 commit comments

Comments
 (0)