Summary: This time it's personal. Roll out pulse's own arithmetic domain to be fast and be able to add precision as needed. Formulas are precise representations of the path condition to allow for good inter-procedural precision. Reasoning on these is somewhat ad-hoc (except for equalities, but even these aren't quite properly saturated in general), so expect lots of holes. Skipping dead code in the interest of readability as this (at least temporarily) doesn't use pudge anymore. This may make a come-back as pudge has/will have better precision: the proposed implementation of `PulseFormula` is very cheap so can be used any time we could want to prune paths (see following commits), but this comes at the price of some precision. Calling into pudge at reporting time still sounds like a good idea to reduce false positives due to infeasible paths. #skipdeadcode Reviewed By: skcho Differential Revision: D22576004 fbshipit-source-id: c91793256master
parent
e4a7d1f19d
commit
5a39c158c5
@ -0,0 +1,101 @@
|
|||||||
|
(*
|
||||||
|
* Copyright (c) Facebook, Inc. and its affiliates.
|
||||||
|
*
|
||||||
|
* This source code is licensed under the MIT license found in the
|
||||||
|
* LICENSE file in the root directory of this source tree.
|
||||||
|
*)
|
||||||
|
|
||||||
|
open! IStd
|
||||||
|
|
||||||
|
module type Element = sig
|
||||||
|
type t [@@deriving compare]
|
||||||
|
|
||||||
|
val is_simpler_than : t -> t -> bool
|
||||||
|
end
|
||||||
|
|
||||||
|
module Make (X : Element) = struct
|
||||||
|
module Set = Caml.Set.Make (X)
|
||||||
|
module Map = Caml.Map.Make (X)
|
||||||
|
|
||||||
|
let equal_x = [%compare.equal: X.t]
|
||||||
|
|
||||||
|
(** the union-find backing data structure: maps elements to their representatives *)
|
||||||
|
module UF : sig
|
||||||
|
(** to get a little bit of type safety *)
|
||||||
|
type repr = private X.t
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val empty : t
|
||||||
|
|
||||||
|
val find_opt : t -> X.t -> repr option
|
||||||
|
|
||||||
|
val find : t -> X.t -> repr
|
||||||
|
|
||||||
|
val merge : t -> repr -> into:repr -> t
|
||||||
|
|
||||||
|
module Map : Caml.Map.S with type key = repr
|
||||||
|
end = struct
|
||||||
|
type repr = X.t
|
||||||
|
|
||||||
|
type t = X.t Map.t
|
||||||
|
|
||||||
|
let empty = Map.empty
|
||||||
|
|
||||||
|
let find_opt reprs x =
|
||||||
|
let rec find_opt_aux candidate_repr =
|
||||||
|
(* [x] is in the relation and now we are climbing up to the final representative *)
|
||||||
|
match Map.find_opt candidate_repr reprs with
|
||||||
|
| None ->
|
||||||
|
(* [candidate_repr] is the representative *)
|
||||||
|
candidate_repr
|
||||||
|
| Some candidate_repr' ->
|
||||||
|
(* keep climbing *)
|
||||||
|
find_opt_aux candidate_repr'
|
||||||
|
in
|
||||||
|
Map.find_opt x reprs |> Option.map ~f:find_opt_aux
|
||||||
|
|
||||||
|
|
||||||
|
let find reprs x = find_opt reprs x |> Option.value ~default:x
|
||||||
|
|
||||||
|
let merge reprs x ~into:y = (* TODO: implement path compression *) Map.add x y reprs
|
||||||
|
|
||||||
|
module Map = Map
|
||||||
|
end
|
||||||
|
|
||||||
|
type repr = UF.repr
|
||||||
|
|
||||||
|
module Classes = struct
|
||||||
|
let find classes (x : UF.repr) = UF.Map.find_opt x classes |> Option.value ~default:Set.empty
|
||||||
|
|
||||||
|
let merge classes (x1 : UF.repr) ~into:(x2 : UF.repr) =
|
||||||
|
let class1 = find classes x1 in
|
||||||
|
let class2 = find classes x2 in
|
||||||
|
let new_class = Set.union class1 class2 |> Set.add (x1 :> X.t) in
|
||||||
|
UF.Map.remove x1 classes |> UF.Map.add x2 new_class
|
||||||
|
end
|
||||||
|
|
||||||
|
type t = {reprs: UF.t; classes: Set.t UF.Map.t}
|
||||||
|
|
||||||
|
let empty = {reprs= UF.empty; classes= UF.Map.empty}
|
||||||
|
|
||||||
|
let find_opt uf x = UF.find_opt uf.reprs x
|
||||||
|
|
||||||
|
let find uf x = UF.find uf.reprs x
|
||||||
|
|
||||||
|
let union uf x1 x2 =
|
||||||
|
let repr1 = find uf x1 in
|
||||||
|
let repr2 = find uf x2 in
|
||||||
|
if equal_x (repr1 :> X.t) (repr2 :> X.t) then (* avoid creating loops in the relation *) uf
|
||||||
|
else
|
||||||
|
let from, into =
|
||||||
|
if X.is_simpler_than (repr1 :> X.t) (repr2 :> X.t) then (repr2, repr1) else (repr1, repr2)
|
||||||
|
in
|
||||||
|
let reprs = UF.merge uf.reprs from ~into in
|
||||||
|
let classes = Classes.merge uf.classes from ~into in
|
||||||
|
{reprs; classes}
|
||||||
|
|
||||||
|
|
||||||
|
let fold_congruences {classes} ~init ~f =
|
||||||
|
UF.Map.fold (fun repr xs acc -> f acc (repr, xs)) classes init
|
||||||
|
end
|
@ -0,0 +1,38 @@
|
|||||||
|
(*
|
||||||
|
* Copyright (c) Facebook, Inc. and its affiliates.
|
||||||
|
*
|
||||||
|
* This source code is licensed under the MIT license found in the
|
||||||
|
* LICENSE file in the root directory of this source tree.
|
||||||
|
*)
|
||||||
|
|
||||||
|
open! IStd
|
||||||
|
|
||||||
|
(** A union-find data structure. *)
|
||||||
|
|
||||||
|
module type Element = sig
|
||||||
|
type t [@@deriving compare]
|
||||||
|
|
||||||
|
val is_simpler_than : t -> t -> bool
|
||||||
|
(** will be used to choose a "simpler" representative for a given equivalence class when possible *)
|
||||||
|
end
|
||||||
|
|
||||||
|
module Make (X : Element) : sig
|
||||||
|
type t
|
||||||
|
|
||||||
|
type repr = private X.t
|
||||||
|
|
||||||
|
module Set : Caml.Set.S with type elt = X.t
|
||||||
|
|
||||||
|
val empty : t
|
||||||
|
|
||||||
|
val union : t -> X.t -> X.t -> t
|
||||||
|
|
||||||
|
val find_opt : t -> X.t -> repr option
|
||||||
|
|
||||||
|
val find : t -> X.t -> repr
|
||||||
|
(** like [find_opt] but returns the element given if it wasn't found in the relation *)
|
||||||
|
|
||||||
|
val fold_congruences : (t, repr * Set.t, 'acc) Container.fold
|
||||||
|
(** fold over the equivalence classes of the relation, singling out the representative for each
|
||||||
|
class *)
|
||||||
|
end
|
@ -0,0 +1,71 @@
|
|||||||
|
(*
|
||||||
|
* Copyright (c) Facebook, Inc. and its affiliates.
|
||||||
|
*
|
||||||
|
* This source code is licensed under the MIT license found in the
|
||||||
|
* LICENSE file in the root directory of this source tree.
|
||||||
|
*)
|
||||||
|
|
||||||
|
open! IStd
|
||||||
|
module F = Format
|
||||||
|
module AbstractValue = PulseAbstractValue
|
||||||
|
|
||||||
|
(** {2 Arithmetic solver}
|
||||||
|
|
||||||
|
Build formulas from SIL and tries to decide if they are (mostly un-)satisfiable. *)
|
||||||
|
|
||||||
|
module Term : sig
|
||||||
|
(** Similar to {!Exp.t} but with no memory operations and with {!AbstractValue.t} instead of SIL
|
||||||
|
variables. The rich structure allows us to represent all of SIL but is not a promise that we
|
||||||
|
are able to meaningfully reason about all of it. *)
|
||||||
|
type t
|
||||||
|
|
||||||
|
val zero : t
|
||||||
|
|
||||||
|
val of_absval : AbstractValue.t -> t
|
||||||
|
|
||||||
|
val of_intlit : IntLit.t -> t
|
||||||
|
|
||||||
|
val of_binop : Binop.t -> t -> t -> t
|
||||||
|
|
||||||
|
val of_unop : Unop.t -> t -> t
|
||||||
|
end
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp : F.formatter -> t -> unit
|
||||||
|
|
||||||
|
(** {3 Build formulas from non-formulas} *)
|
||||||
|
|
||||||
|
val ttrue : t
|
||||||
|
|
||||||
|
val of_term_binop : Binop.t -> Term.t -> Term.t -> t
|
||||||
|
|
||||||
|
val mk_equal : Term.t -> Term.t -> t
|
||||||
|
|
||||||
|
val mk_less_equal : Term.t -> Term.t -> t
|
||||||
|
|
||||||
|
val mk_less_than : Term.t -> Term.t -> t
|
||||||
|
|
||||||
|
(** {3 Combine formulas} *)
|
||||||
|
|
||||||
|
val aand : t -> t -> t
|
||||||
|
|
||||||
|
val nnot : t -> t
|
||||||
|
|
||||||
|
(** {3 Operations} *)
|
||||||
|
|
||||||
|
val simplify : keep:AbstractValue.Set.t -> t -> t
|
||||||
|
|
||||||
|
val fold_map_variables : t -> init:'a -> f:('a -> AbstractValue.t -> 'a * AbstractValue.t) -> 'a * t
|
||||||
|
|
||||||
|
val is_literal_false : t -> bool
|
||||||
|
(** Call [is_literal_false (normalize phi)] to check satisfiability. *)
|
||||||
|
|
||||||
|
val normalize : t -> t
|
||||||
|
(** Produces a semantically-equivalent formula¹ where all consequences of equalities have been
|
||||||
|
applied and some ad-hoc arithmetic and logical reasoning has been performed. In particular, the
|
||||||
|
canonical representation of a known-false formula is [ffalse], and [is_literal_false ffalse] is
|
||||||
|
[true]. Probably a good idea to not throw away the result of calling this if you are going to
|
||||||
|
re-use the formula.
|
||||||
|
|
||||||
|
(¹) Except it might throw away disjuncts! *)
|
Loading…
Reference in new issue