@@ -72,16 +72,26 @@ normArgs sym conc l r = case (l, r) of
72
72
where
73
73
doOp = op2 sym conc
74
74
75
+ -- Same as `normArgs`, but for commutative operators it orders the arguments canonically
76
+ -- This helps in cases when (PEq x1 x2) is comparing x1 and x2 that are equivalent modulo commutativity.
77
+ -- In such cases, normArgsOrd will make sure x1 and x2 look the same.
78
+ -- NOTE: This is compatible with `Lit` being always on the left, as `Lit` is always
79
+ -- less than any other expression
80
+ normArgsOrd :: (Expr EWord -> Expr EWord -> Expr EWord ) -> (W256 -> W256 -> W256 ) -> Expr EWord -> Expr EWord -> Expr EWord
81
+ normArgsOrd sym conc l r = if l <= r then doOp l r else doOp r l
82
+ where
83
+ doOp = op2 sym conc
84
+
75
85
-- Integers
76
86
77
87
add :: Expr EWord -> Expr EWord -> Expr EWord
78
- add = normArgs Add (+)
88
+ add = normArgsOrd Add (+)
79
89
80
90
sub :: Expr EWord -> Expr EWord -> Expr EWord
81
91
sub = op2 Sub (-)
82
92
83
93
mul :: Expr EWord -> Expr EWord -> Expr EWord
84
- mul = normArgs Mul (*)
94
+ mul = normArgsOrd Mul (*)
85
95
86
96
div :: Expr EWord -> Expr EWord -> Expr EWord
87
97
div = op2 Div (\ x y -> if y == 0 then 0 else Prelude. div x y)
@@ -156,21 +166,21 @@ sgt = op2 SGT (\x y ->
156
166
in if sx > sy then 1 else 0 )
157
167
158
168
eq :: Expr EWord -> Expr EWord -> Expr EWord
159
- eq = normArgs Eq (\ x y -> if x == y then 1 else 0 )
169
+ eq = normArgsOrd Eq (\ x y -> if x == y then 1 else 0 )
160
170
161
171
iszero :: Expr EWord -> Expr EWord
162
172
iszero = op1 IsZero (\ x -> if x == 0 then 1 else 0 )
163
173
164
174
-- Bits
165
175
166
176
and :: Expr EWord -> Expr EWord -> Expr EWord
167
- and = normArgs And (.&.)
177
+ and = normArgsOrd And (.&.)
168
178
169
179
or :: Expr EWord -> Expr EWord -> Expr EWord
170
- or = normArgs Or (.|.)
180
+ or = normArgsOrd Or (.|.)
171
181
172
182
xor :: Expr EWord -> Expr EWord -> Expr EWord
173
- xor = normArgs Xor Data.Bits. xor
183
+ xor = normArgsOrd Xor Data.Bits. xor
174
184
175
185
not :: Expr EWord -> Expr EWord
176
186
not = op1 Not complement
@@ -706,9 +716,9 @@ pattern MappingSlot :: ByteString -> Expr EWord -> Expr EWord
706
716
pattern MappingSlot idx key = Keccak (WriteWord (Lit 0 ) key (ConcreteBuf idx))
707
717
708
718
-- storage slots for arrays are determined by (keccak(bytes32(id)) + offset)
709
- -- note that `normArgs` puts the Lit as the 2nd argument to `Add`
719
+ -- note that `normArgs` puts the Lit as the 1st argument to `Add`
710
720
pattern ArraySlotWithOffs :: ByteString -> Expr EWord -> Expr EWord
711
- pattern ArraySlotWithOffs id offset = Add (Keccak (ConcreteBuf id )) offset
721
+ pattern ArraySlotWithOffs id offset = Add offset (Keccak (ConcreteBuf id ))
712
722
713
723
-- special pattern to match the 0th element because the `Add` term gets simplified out
714
724
pattern ArraySlotZero :: ByteString -> Expr EWord
@@ -1063,9 +1073,6 @@ simplify e = if (mapExpr go e == e)
1063
1073
-- literal addresses
1064
1074
go (WAddr (LitAddr a)) = Lit $ into a
1065
1075
1066
- -- XOR normalization
1067
- go (Xor a b) = EVM.Expr. xor a b
1068
-
1069
1076
-- simple div/mod/add/sub
1070
1077
go (Div o1@ (Lit _) o2@ (Lit _)) = EVM.Expr. div o1 o2
1071
1078
go (SDiv o1@ (Lit _) o2@ (Lit _)) = EVM.Expr. sdiv o1 o2
@@ -1094,7 +1101,6 @@ simplify e = if (mapExpr go e == e)
1094
1101
-- Notice: all Add is normalized, hence the 1st argument is
1095
1102
-- expected to be Lit, if any. Hence `orig` needs to be the
1096
1103
-- 2nd argument for Add. However, Sub is not normalized
1097
- go (Add (Lit x) (Add (Lit y) orig)) = add (Lit (x+ y)) orig
1098
1104
-- add + sub NOTE: every combination of Sub is needed (2)
1099
1105
go (Add (Lit x) (Sub (Lit y) orig)) = sub (Lit (x+ y)) orig
1100
1106
go (Add (Lit x) (Sub orig (Lit y))) = add (Lit (x- y)) orig
@@ -1107,18 +1113,33 @@ simplify e = if (mapExpr go e == e)
1107
1113
go (Sub (Lit x) (Add (Lit y) orig)) = sub (Lit (x- y)) orig
1108
1114
go (Sub (Add (Lit x) orig) (Lit y) ) = add (Lit (x- y)) orig
1109
1115
1116
+ -- Add+Add / Mul+Mul / Xor+Xor simplifications, taking
1117
+ -- advantage of associativity and commutativity
1118
+ -- Since Lit is smallest in the ordering, it will always be the first argument
1119
+ -- hence these will collect Lits. See `simp-assoc..` tests
1120
+ go (Add (Lit a) (Add (Lit b) x)) = add (Lit (a+ b)) x
1121
+ go (Mul (Lit a) (Mul (Lit b) x)) = mul (Lit (a* b)) x
1122
+ go (Xor (Lit a) (Xor (Lit b) x)) = EVM.Expr. xor (Lit (Data.Bits. xor a b)) x
1123
+ go (Add a (Add b c)) = add (l !! 0 ) (add (l !! 1 ) (l !! 2 ))
1124
+ where l = sort [a, b, c]
1125
+ go (Mul a (Mul b c)) = mul (l !! 0 ) (mul (l !! 1 ) (l !! 2 ))
1126
+ where l = sort [a, b, c]
1127
+ go (Xor a (Xor b c)) = x (l !! 0 ) (x (l !! 1 ) (l !! 2 ))
1128
+ where l = sort [a, b, c]
1129
+ x = EVM.Expr. xor
1130
+ go (Or a (Or b c)) = o (l !! 0 ) (o (l !! 1 ) (l !! 2 ))
1131
+ where l = sort [a, b, c]
1132
+ o = EVM.Expr. or
1133
+ go (And a (And b c)) = an (l !! 0 ) (an (l !! 1 ) (l !! 2 ))
1134
+ where l = sort [a, b, c]
1135
+ an = EVM.Expr. and
1136
+
1110
1137
-- redundant add / sub
1111
1138
go (Sub (Add a b) c)
1112
1139
| a == c = b
1113
1140
| b == c = a
1114
1141
| otherwise = sub (add a b) c
1115
1142
1116
- -- Add is associative. We are doing left-growing trees because LIT is
1117
- -- arranged to the left. This way, they accumulate in all combinations.
1118
- -- See `sim-assoc-add` test cases in test.hs
1119
- go (Add a (Add b c)) = add (add a b) c
1120
- go (Add (Add (Lit a) x) (Lit b)) = add (Lit (a+ b)) x
1121
-
1122
1143
-- add / sub identities
1123
1144
go (Add a b)
1124
1145
| b == (Lit 0 ) = a
@@ -1129,6 +1150,9 @@ simplify e = if (mapExpr go e == e)
1129
1150
| b == (Lit 0 ) = a
1130
1151
| otherwise = sub a b
1131
1152
1153
+ -- XOR normalization
1154
+ go (Xor a b) = EVM.Expr. xor a b
1155
+
1132
1156
-- SHL / SHR by 0
1133
1157
go (SHL a v)
1134
1158
| a == (Lit 0 ) = v
@@ -1137,12 +1161,6 @@ simplify e = if (mapExpr go e == e)
1137
1161
| a == (Lit 0 ) = v
1138
1162
| otherwise = shr a v
1139
1163
1140
- -- doubled And
1141
- go o@ (And a (And b c))
1142
- | a == c = (And a b)
1143
- | a == b = (And b c)
1144
- | otherwise = o
1145
-
1146
1164
-- Bitwise AND & OR. These MUST preserve bitwise equivalence
1147
1165
go (And a b)
1148
1166
| a == b = a
@@ -1182,11 +1200,6 @@ simplify e = if (mapExpr go e == e)
1182
1200
(Lit 0 , _) -> Lit 0
1183
1201
_ -> EVM.Expr. min a b
1184
1202
1185
- -- Mul is associative. We are doing left-growing trees because LIT is
1186
- -- arranged to the left. This way, they accumulate in all combinations.
1187
- -- See `sim-assoc-add` test cases in test.hs
1188
- go (Mul a (Mul b c)) = mul (mul a b) c
1189
- go (Mul (Mul (Lit a) x) (Lit b)) = mul (Lit (a* b)) x
1190
1203
1191
1204
-- Some trivial mul eliminations
1192
1205
go (Mul a b) = case (a, b) of
@@ -1268,6 +1281,10 @@ simplifyProp prop =
1268
1281
-- negations
1269
1282
go (PNeg (PBool b)) = PBool (Prelude. not b)
1270
1283
go (PNeg (PNeg a)) = a
1284
+ go (PNeg (PGT a b)) = PLEq a b
1285
+ go (PNeg (PGEq a b)) = PLT a b
1286
+ go (PNeg (PLT a b)) = PGEq a b
1287
+ go (PNeg (PLEq a b)) = PGT a b
1271
1288
1272
1289
-- Empty buf
1273
1290
go (PEq (Lit 0 ) (BufLength k)) = peq k (ConcreteBuf " " )
0 commit comments