Skip to content

Commit

Permalink
refactor(sat): remove useless argument of [Decided]
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>

<!-- ps-id: 42c78b9f-bdbf-43fd-8253-2a58050a7e03 -->

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Jan 31, 2025
1 parent 45d421f commit 85f7585
Showing 1 changed file with 6 additions and 6 deletions.
12 changes: 6 additions & 6 deletions src/sat/sat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ module Make (User : USER) = struct

and undo =
| Undo_at_most_one of lit option ref
| Decided of t
| Decided

and var =
{ id : VarID.t (* A unique ID, used to test identity *)
Expand All @@ -130,7 +130,7 @@ module Make (User : USER) = struct

and lit = sign * var

and t =
type t =
{ id_maker : VarID.mint
; (* Propagation *)
mutable vars : var list
Expand Down Expand Up @@ -245,9 +245,9 @@ module Make (User : USER) = struct
| Neg -> Pp.text "not(" ++ User.pp var.obj ++ Pp.char ')'
;;

let undo undo lit =
let undo problem undo lit =
match undo with
| Decided problem -> problem.set_to_false <- false
| Decided -> problem.set_to_false <- false
| Undo_at_most_one current ->
if debug
then
Expand Down Expand Up @@ -342,7 +342,7 @@ module Make (User : USER) = struct
while var_info.undo <> [] do
let cb = List.hd var_info.undo in
var_info.undo <- List.tl var_info.undo;
undo cb lit
undo problem cb lit
done
;;

Expand Down Expand Up @@ -876,7 +876,7 @@ module Make (User : USER) = struct
| None ->
(* Switch to set_to_false mode (until we backtrack). *)
problem.set_to_false <- true;
undecided.undo <- Decided problem :: undecided.undo;
undecided.undo <- Decided :: undecided.undo;
(* Printf.printf "%s -> false\n" (name_lit undecided); *)
Neg, undecided)
in
Expand Down

0 comments on commit 85f7585

Please sign in to comment.