Skip to content

Commit

Permalink
refactor(sat): simplify solution type (#11394)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Jan 26, 2025
1 parent bc877f6 commit e32e82d
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 10 deletions.
16 changes: 7 additions & 9 deletions src/sat/sat.ml
Original file line number Diff line number Diff line change
Expand Up @@ -167,7 +167,7 @@ module Make (User : USER) = struct
;;
end

type solution = lit -> bool
type solution = unit

let make_var id obj =
{ id
Expand Down Expand Up @@ -206,7 +206,7 @@ module Make (User : USER) = struct
;;

exception ConflictingClause of clause
exception SolveDone of solution option
exception SolveDone of bool

type added_result =
| AddedFact of bool (* Result of enqueing the new fact *)
Expand Down Expand Up @@ -253,6 +253,7 @@ module Make (User : USER) = struct
| Neg -> Var_value.invert var.value
;;

let value () lit = Var_value.assignment_exn (lit_value lit)
let get_user_data_for_lit lit = (var_of_lit lit).obj

let pp_lit_assignment l =
Expand Down Expand Up @@ -832,11 +833,7 @@ module Make (User : USER) = struct
let undecided =
match List.find problem.vars ~f:(fun info -> info.value = Undecided) with
| Some s -> s
| None ->
(* Everything is assigned without conflicts *)
(* if debug then log_debug "SUCCESS!"; *)
raise_notrace
(SolveDone (Some (fun var -> Var_value.assignment_exn (lit_value var))))
| None -> raise_notrace (SolveDone true)
in
let lit =
if problem.set_to_false
Expand Down Expand Up @@ -868,7 +865,7 @@ module Make (User : USER) = struct
if get_decision_level problem = 0
then (
if debug then log_debug (Pp.text "FAIL: conflict found at top level");
raise_notrace (SolveDone None))
raise_notrace (SolveDone false))
else (
(* Figure out the root cause of this failure. *)
let learnt, backtrack_level = analyse problem conflicting_clause in
Expand All @@ -894,7 +891,8 @@ module Make (User : USER) = struct
done;
Code_error.raise "not reached" []
with
| SolveDone x -> x)
| SolveDone true -> Some ()
| SolveDone false -> None)
;;

let pp_lit_reason lit =
Expand Down
4 changes: 3 additions & 1 deletion src/sat/sat.mli
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,9 @@ module Make (User : USER) : sig
val create : unit -> t

(** Get the assignment for this literal in the discovered solution. *)
type solution = lit -> bool
type solution

val value : solution -> lit -> bool

(** Indicate that the problem is unsolvable, before even starting. This is a convenience
feature so that clients don't need a separate code path for problems they discover
Expand Down

0 comments on commit e32e82d

Please sign in to comment.