[cleanup] Simplify PrettyPrintable.Make functors

Summary: Being forced to separately define `pp_element`/`pp_key` is uneccessary and makes it more cumbersome to create a set/map from an existing module that already defines `pp`.

Reviewed By: jeremydubreil

Differential Revision: D4517308

fbshipit-source-id: 9b17c9c
master
Sam Blackshear 8 years ago committed by Facebook Github Bot
parent c902068c4f
commit a4efc7bba7

@ -32,7 +32,7 @@ let pp fmt annotation => F.fprintf fmt "@@%s" annotation.class_name;
let module Map = PrettyPrintable.MakePPMap {
type nonrec t = t;
let compare = compare;
let pp_key = pp;
let pp = pp;
};
let module Item = {

@ -38,5 +38,5 @@ let pp fmt t =
module Set = PrettyPrintable.MakePPSet(struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)

@ -364,5 +364,5 @@ let module Set = PrettyPrintable.MakePPCompareSet {
type nonrec t = t;
let compare = compare;
let compare_pp = compare_alpha;
let pp_element = pp Pp.text;
let pp = pp Pp.text;
};

@ -13,16 +13,10 @@ module F = Format
(** Wrappers for making pretty-printable modules *)
module type SetOrderedType = sig
module type PrintableOrderedType = sig
include Caml.Set.OrderedType
val pp_element : F.formatter -> t -> unit
end
module type MapOrderedType = sig
include Caml.Map.OrderedType
val pp_key : F.formatter -> t -> unit
val pp : F.formatter -> t -> unit
end
module type PPSet = sig
@ -45,32 +39,32 @@ let pp_collection ~pp_item fmt c =
F.pp_print_list ~pp_sep pp_item fmt c in
F.fprintf fmt "{ %a }" pp_collection c
module MakePPSet (Ord : SetOrderedType) = struct
module MakePPSet (Ord : PrintableOrderedType) = struct
include Caml.Set.Make(Ord)
let pp_element = Ord.pp_element
let pp_element = Ord.pp
let pp fmt s =
pp_collection ~pp_item:pp_element fmt (elements s)
end
module MakePPCompareSet
(Ord : sig include SetOrderedType val compare_pp : t -> t -> int end) = struct
(Ord : sig include PrintableOrderedType val compare_pp : t -> t -> int end) = struct
include Caml.Set.Make(Ord)
let pp_element = Ord.pp_element
let pp_element = Ord.pp
let pp fmt s =
let elements_alpha = IList.sort Ord.compare_pp (elements s) in
pp_collection ~pp_item:pp_element fmt elements_alpha
end
module MakePPMap (Ord : MapOrderedType) = struct
module MakePPMap (Ord : PrintableOrderedType) = struct
include Caml.Map.Make(Ord)
let pp_key = Ord.pp_key
let pp_key = Ord.pp
let pp ~pp_value fmt m =
let pp_item fmt (k, v) = F.fprintf fmt "%a -> %a" Ord.pp_key k pp_value v in
let pp_item fmt (k, v) = F.fprintf fmt "%a -> %a" Ord.pp k pp_value v in
pp_collection ~pp_item fmt (bindings m)
end

@ -15,16 +15,10 @@ module F = Format
val pp_collection : pp_item:(F.formatter -> 'a -> unit) -> F.formatter -> 'a list -> unit
module type SetOrderedType = sig
type t
val compare : t -> t -> int
val pp_element : F.formatter -> t -> unit
end
module type PrintableOrderedType = sig
include Caml.Set.OrderedType
module type MapOrderedType = sig
type t
val compare : t -> t -> int
val pp_key : F.formatter -> t -> unit
val pp : F.formatter -> t -> unit
end
module type PPSet = sig
@ -39,14 +33,14 @@ module type PPMap = sig
val pp : pp_value:(F.formatter -> 'a -> unit) -> F.formatter -> 'a t -> unit
end
module MakePPSet (Ord : SetOrderedType) : (PPSet with type elt = Ord.t)
module MakePPSet (Ord : PrintableOrderedType) : (PPSet with type elt = Ord.t)
(** Use a comparison function to determine the order of the elements printed *)
module MakePPCompareSet
(Ord : sig
include SetOrderedType
include PrintableOrderedType
val compare_pp : t -> t -> int
end)
: (PPSet with type elt = Ord.t)
module MakePPMap (Ord : MapOrderedType) : (PPMap with type key = Ord.t)
module MakePPMap (Ord : PrintableOrderedType) : (PPMap with type key = Ord.t)

@ -65,9 +65,6 @@ let pp : F.formatter -> t -> unit
Itv.pp c.idx Itv.pp c.size pp_location c pname (string_of_location loc)
| Intra _ -> F.fprintf fmt "%a < %a at %a" Itv.pp c.idx Itv.pp c.size pp_location c
let pp_element : F.formatter -> t -> unit
= pp
let get_location : t -> Location.t
= fun c -> c.loc
@ -391,8 +388,7 @@ module Stack =
struct
module PPMap =
struct
module Ord = struct include Loc let pp_key = pp end
include PrettyPrintable.MakePPMap (Ord)
include PrettyPrintable.MakePPMap (Loc)
let pp_collection
: pp_item:(F.formatter -> 'a -> unit) -> F.formatter -> 'a list -> unit
@ -404,7 +400,7 @@ struct
: pp_value:(F.formatter -> 'a -> unit) -> F.formatter -> 'a t -> unit
= fun ~pp_value fmt m ->
let pp_item fmt (k, v) =
F.fprintf fmt "%a -> %a" Ord.pp_key k pp_value v
F.fprintf fmt "%a -> %a" Loc.pp k pp_value v
in
F.fprintf fmt "@[<v 2>{ ";
pp_collection ~pp_item fmt (bindings m);
@ -446,8 +442,7 @@ module Heap =
struct
module PPMap =
struct
module Ord = struct include Loc let pp_key = pp end
include PrettyPrintable.MakePPMap (Ord)
include PrettyPrintable.MakePPMap (Loc)
let pp_collection
: pp_item:(F.formatter -> 'a -> unit) -> F.formatter -> 'a list -> unit
@ -458,7 +453,7 @@ struct
let pp : pp_value:(F.formatter -> 'a -> unit) -> F.formatter -> 'a t -> unit
= fun ~pp_value fmt m ->
let pp_item fmt (k, v) =
F.fprintf fmt "%a -> %a" Ord.pp_key k pp_value v
F.fprintf fmt "%a -> %a" Loc.pp k pp_value v
in
F.fprintf fmt "@[<v 2>{ ";
pp_collection ~pp_item fmt (bindings m);

@ -14,11 +14,7 @@ module L = Logging
(** find transitive procedure calls for each procedure *)
module ProcnameSet = PrettyPrintable.MakePPSet(struct
type t = Procname.t
let compare = Procname.compare
let pp_element = Procname.pp
end)
module ProcnameSet = PrettyPrintable.MakePPSet(Procname)
module Domain = AbstractDomain.FiniteSet(ProcnameSet)

@ -31,5 +31,5 @@ let pp fmt s =
module Set = PrettyPrintable.MakePPSet(struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)

@ -50,7 +50,7 @@ module Make (Spec : Spec) : S = struct
struct
type t = Spec.astate
let compare = Spec.compare
let pp_element _ _ = ()
let pp _ _ = ()
end)
)

@ -86,6 +86,6 @@ module Make (Kind : Kind) = struct
module Set = PrettyPrintable.MakePPSet(struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)
end

@ -18,7 +18,7 @@ module GlobalsAccesses = PrettyPrintable.MakePPSet (struct
let compare (v1, l1) (v2, l2) =
(* compare by loc first to present reports in the right order *)
[%compare : (Location.t * Pvar.t)] (l1, v1) (l2, v2)
let pp_element fmt (v, _) =
let pp fmt (v, _) =
F.fprintf fmt "%a" Mangled.pp (Pvar.get_name v);
match Pvar.get_source_file v with
| Some fname -> F.fprintf fmt "%a" SourceFile.pp fname
@ -54,7 +54,7 @@ module TraceElem = struct
(* type nonrec t = t [@@deriving compare]; *)
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)
end

@ -99,7 +99,7 @@ module Make (Kind : Kind) = struct
module Set = PrettyPrintable.MakePPSet(struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)
end
@ -133,7 +133,7 @@ module Dummy = struct
module Set = PrettyPrintable.MakePPSet(struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)
let with_callsite t _ = t

@ -35,7 +35,7 @@ module TraceElem = struct
module Set = PrettyPrintable.MakePPSet (struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)
end
@ -47,11 +47,7 @@ module LocksDomain = AbstractDomain.BooleanAnd
module PathDomain = SinkTrace.Make(TraceElem)
module IntMap = PrettyPrintable.MakePPMap(struct
type t = int
let compare = Int.compare
let pp_key fmt = F.fprintf fmt "%d"
end)
module IntMap = PrettyPrintable.MakePPMap(Int)
module ConditionalWritesDomain = AbstractDomain.Map (IntMap) (PathDomain)

@ -151,17 +151,13 @@ let pp fmt = function
module BaseMap = PrettyPrintable.MakePPMap(struct
type t = base
let compare = compare_base
let pp_key = pp_base
let pp = pp_base
end)
module AccessMap = PrettyPrintable.MakePPMap(struct
type t = access
let compare = compare_access
let pp_key = pp_access
let pp = pp_access
end)
module RawSet = PrettyPrintable.MakePPSet(struct
type t = Raw.t
let compare = Raw.compare
let pp_element = Raw.pp
end)
module RawSet = PrettyPrintable.MakePPSet(Raw)

@ -12,11 +12,7 @@ open! IStd
module F = Format
module Set = struct
module APSet = PrettyPrintable.MakePPSet (struct
type t = AccessPath.t
let compare = AccessPath.compare
let pp_element = AccessPath.pp
end)
module APSet = PrettyPrintable.MakePPSet (AccessPath)
(** TODO (12086310): best-case behavior of some operations can be improved by adding "abstracted"
bool recording whether an abstracted access path has been introduced *)

@ -39,12 +39,12 @@ let pp fmt = function
module Map = PrettyPrintable.MakePPMap(struct
type nonrec t = t
let compare = compare
let pp_key = pp
let pp = pp
end)
module Set = PrettyPrintable.MakePPCompareSet(struct
type nonrec t = t
let compare = compare
let compare_pp = compare_alpha
let pp_element = pp
let pp = pp
end)

@ -43,7 +43,7 @@ module MockTraceElem = struct
module Set = PrettyPrintable.MakePPSet(struct
type nonrec t = t
let compare = compare
let pp_element = pp
let pp = pp
end)
let with_callsite t _ = t

Loading…
Cancel
Save