Skip to content

Commit b4bf4b9

Browse files
authored
refactor(pkg): cache transient sets (#11398)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 2f96ee5 commit b4bf4b9

File tree

1 file changed

+15
-4
lines changed

1 file changed

+15
-4
lines changed

src/sat/sat.ml

+15-4
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ module VarID : sig
4242
val create : unit -> t
4343
val mem : t -> id -> bool
4444
val add : t -> id -> unit
45+
val clear : t -> unit
4546
end
4647
end = struct
4748
type t = int
@@ -153,6 +154,12 @@ module Make (User : USER) = struct
153154
}
154155

155156
let create () = { pos = VarID.Hash_set.create (); neg = VarID.Hash_set.create () }
157+
let temp = create ()
158+
159+
let clear () =
160+
VarID.Hash_set.clear temp.pos;
161+
VarID.Hash_set.clear temp.neg
162+
;;
156163

157164
let mem { pos; neg } (sign, lit) =
158165
match sign with
@@ -194,7 +201,8 @@ module Make (User : USER) = struct
194201
;;
195202

196203
let remove_duplicates lits =
197-
let seen = LitSet.create () in
204+
LitSet.clear ();
205+
let seen = LitSet.temp in
198206
let rec find_unique = function
199207
| [] -> []
200208
| x :: xs when LitSet.mem seen x -> find_unique xs
@@ -454,13 +462,13 @@ module Make (User : USER) = struct
454462
enqueue problem lits.(0) (Clause t))
455463
else (
456464
match lit_value lits.(i) with
465+
| False -> find_not_false (i + 1)
457466
| Undecided | True ->
458467
(* If it's True then we've already done our job,
459468
so this means we don't get notified unless we backtrack, which is fine. *)
460469
Array.swap lits 1 i;
461470
watch_lit (neg lits.(1)) t;
462-
true
463-
| False -> find_not_false (i + 1))
471+
true)
464472
in
465473
find_not_false 2)
466474
| At_most_one (current, problem, lits) ->
@@ -595,7 +603,10 @@ module Make (User : USER) = struct
595603
then (* Trivially true already if any literal is True. *)
596604
()
597605
else (
598-
let seen = LitSet.create () in
606+
let seen =
607+
LitSet.clear ();
608+
LitSet.temp
609+
in
599610
let rec simplify unique = function
600611
| [] -> Some unique
601612
| x :: _ when LitSet.mem seen (neg x) -> None (* X or not(X) is always True *)

0 commit comments

Comments
 (0)