Skip to content

Commit 580256f

Browse files
authored
refactor(sat): move simpify to own function (#11414)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent a2e4f4d commit 580256f

File tree

1 file changed

+19
-15
lines changed

1 file changed

+19
-15
lines changed

src/sat/sat.ml

+19-15
Original file line numberDiff line numberDiff line change
@@ -603,6 +603,24 @@ module Make (User : USER) = struct
603603
AddedClause clause
604604
;;
605605

606+
let simplify lits =
607+
let seen =
608+
LitSet.clear ();
609+
LitSet.temp
610+
in
611+
let rec simplify unique = function
612+
| [] -> Some unique
613+
| x :: _ when LitSet.mem seen (neg x) -> None (* X or not(X) is always True *)
614+
| x :: xs when LitSet.mem seen x -> simplify unique xs (* Skip duplicates *)
615+
| x :: xs when lit_value x = False ->
616+
simplify unique xs (* Skip values known to be False *)
617+
| x :: xs ->
618+
LitSet.add seen x;
619+
simplify (x :: unique) xs
620+
in
621+
simplify [] lits
622+
;;
623+
606624
(** Public interface. Only used before the solve starts. *)
607625
let at_least_one problem ?(reason = "input fact") lits =
608626
if List.is_empty lits
@@ -612,22 +630,8 @@ module Make (User : USER) = struct
612630
then (* Trivially true already if any literal is True. *)
613631
()
614632
else (
615-
let seen =
616-
LitSet.clear ();
617-
LitSet.temp
618-
in
619-
let rec simplify unique = function
620-
| [] -> Some unique
621-
| x :: _ when LitSet.mem seen (neg x) -> None (* X or not(X) is always True *)
622-
| x :: xs when LitSet.mem seen x -> simplify unique xs (* Skip duplicates *)
623-
| x :: xs when lit_value x = False ->
624-
simplify unique xs (* Skip values known to be False *)
625-
| x :: xs ->
626-
LitSet.add seen x;
627-
simplify (x :: unique) xs
628-
in
629633
(* At this point, [unique] contains only [Undefined] literals. *)
630-
match simplify [] lits with
634+
match simplify lits with
631635
| None -> ()
632636
| Some [] ->
633637
problem.toplevel_conflict <- true (* Everything in the list was False *)

0 commit comments

Comments
 (0)