Share NodeId Sets and Maps

Summary:
Let's see in later diffs if that's that useful

Instead of rebuilding these modules, let's share them

Reviewed By: sblackshear

Differential Revision: D7586302

fbshipit-source-id: de69b39
master
Mehdi Bouaziz 7 years ago committed by Facebook Github Bot
parent 7c0bf66794
commit 594ddab2a5

@ -42,7 +42,7 @@ module MakeNoCFG
(TransferFunctions : TransferFunctions.SIL with module CFG = Scheduler.CFG) =
struct
module CFG = Scheduler.CFG
module InvariantMap = ProcCfg.NodeIdMap (CFG)
module InvariantMap = CFG.IdMap
module TransferFunctions = TransferFunctions
module Domain = TransferFunctions.Domain

@ -50,9 +50,9 @@ end
module MakeNoCFG
(Scheduler : Scheduler.S)
(TransferFunctions : TransferFunctions.SIL with module CFG = Scheduler.CFG) :
S with module TransferFunctions = TransferFunctions
S with module TransferFunctions = TransferFunctions and module InvariantMap = Scheduler.CFG.IdMap
(** create an intraprocedural abstract interpreter from a CFG and functors for creating a scheduler/
transfer functions from a CFG *)
module Make (CFG : ProcCfg.S) (MakeTransferFunctions : TransferFunctions.MakeSIL) :
S with module TransferFunctions = MakeTransferFunctions(CFG)
S with module TransferFunctions = MakeTransferFunctions(CFG) and module InvariantMap = CFG.IdMap

@ -34,6 +34,10 @@ module type Node = sig
val compare_id : id -> id -> int
val pp_id : F.formatter -> id -> unit
module IdMap : PrettyPrintable.PPMap with type key = id
module IdSet : PrettyPrintable.PPSet with type elt = id
end
module DefaultNode = struct
@ -54,6 +58,17 @@ module DefaultNode = struct
let compare_id = Procdesc.Node.compare_id
let pp_id = Procdesc.Node.pp_id
module OrderedId = struct
type t = id
let compare = compare_id
let pp = pp_id
end
module IdMap = PrettyPrintable.MakePPMap (OrderedId)
module IdSet = PrettyPrintable.MakePPSet (OrderedId)
end
module InstrNode = struct
@ -84,6 +99,18 @@ module InstrNode = struct
Procdesc.Node.pp_id fmt id
| Instr_index i ->
F.fprintf fmt "(%a: %d)" Procdesc.Node.pp_id id i
module OrderedId = struct
type t = id
let compare = compare_id
let pp = pp_id
end
module IdMap = PrettyPrintable.MakePPMap (OrderedId)
module IdSet = PrettyPrintable.MakePPSet (OrderedId)
end
module type S = sig
@ -275,7 +302,13 @@ end
module OneInstrPerNode (Base : S with type node = Procdesc.Node.t and type id = Procdesc.Node.id) =
struct
include (Base : module type of Base with type id := Procdesc.Node.id and type t = Base.t)
include (
Base :
module type of Base
with type id := Procdesc.Node.id
and type t = Base.t
and module IdMap := Base.IdMap
and module IdSet := Base.IdSet )
type id = Base.id * index
@ -289,15 +322,3 @@ struct
(instr, Some id) )
(instrs t)
end
module NodeIdMap (CFG : S) = Caml.Map.Make (struct
type t = CFG.id
let compare = CFG.compare_id
end)
module NodeIdSet (CFG : S) = Caml.Set.Make (struct
type t = CFG.id
let compare = CFG.compare_id
end)

@ -33,6 +33,10 @@ module type Node = sig
val compare_id : id -> id -> int
val pp_id : Format.formatter -> id -> unit
module IdMap : PrettyPrintable.PPMap with type key = id
module IdSet : PrettyPrintable.PPSet with type elt = id
end
module type S = sig
@ -102,7 +106,3 @@ module Backward (Base : S) : S with type t = Base.t and type node = Base.node an
module OneInstrPerNode (Base : S with type node = DefaultNode.t and type id = DefaultNode.id) :
S with type t = Base.t and type node = Base.node and type id = Base.id * index
module NodeIdMap (CFG : S) : Caml.Map.S with type key = CFG.id
module NodeIdSet (CFG : S) : Caml.Set.S with type elt = CFG.id

@ -34,10 +34,10 @@ end
and conditionals; not as good for loops (may visit nodes after a loop multiple times). *)
module ReversePostorder (CFG : ProcCfg.S) = struct
module CFG = CFG
module M = ProcCfg.NodeIdMap (CFG)
module M = CFG.IdMap
module WorkUnit = struct
module IdSet = ProcCfg.NodeIdSet (CFG)
module IdSet = CFG.IdSet
type t =
{ node: CFG.node (** node whose instructions will be analyzed *)

@ -35,6 +35,17 @@ module MockNode = struct
let compare_id = Int.compare
let pp_id fmt i = F.fprintf fmt "%i" i
module OrderedId = struct
type t = id
let compare = compare_id
let pp = pp_id
end
module IdMap = PrettyPrintable.MakePPMap (OrderedId)
module IdSet = PrettyPrintable.MakePPSet (OrderedId)
end
module MockProcCfg = struct

Loading…
Cancel
Save