diff --git a/.gitignore b/.gitignore index a18e084..cc4417c 100644 --- a/.gitignore +++ b/.gitignore @@ -1,3 +1,4 @@ +out/* *.annot *.cmo *.cma diff --git a/lib/ast/normalize.ml b/lib/ast/normalize.ml index 383c9a1..bc058fe 100644 --- a/lib/ast/normalize.ml +++ b/lib/ast/normalize.ml @@ -850,7 +850,7 @@ and normalize_for_left (left : ('M, 'T) generic_left) : norm_stmt_t * m Statemen [], to_var_decl (List.hd decl_stmts) | LeftPattern pattern -> - let id, decl_stmts = createVariableDeclaration None Location.empty in + let id, decl_stmts = createVariableDeclaration None (Location.empty ()) in let stmts, _ = normalize_pattern (Identifier.to_expression id) pattern None in stmts, to_var_decl (List.hd decl_stmts) diff --git a/lib/ast/structures/functions.ml b/lib/ast/structures/functions.ml new file mode 100644 index 0000000..90924cd --- /dev/null +++ b/lib/ast/structures/functions.ml @@ -0,0 +1,217 @@ +open Auxiliary.Functions + +(* function id definition *) +module Id = struct + + type t = { + uid : int; + name : string; + } + + let create (uid' : int) (name' : string) : t = {uid = uid'; name = name'} + let equal (func_id : t) (func_id' : t) = Int.equal func_id.uid func_id'.uid + && String.equal func_id.name func_id'.name + let hash (func_id : t)= Hashtbl.hash func_id.uid + + let get_id (func_id : t) = func_id.uid + let get_name (func_id : t) = func_id.name + + let to_string (func_id: t) : string = "(" ^ string_of_int func_id.uid ^ ", " ^ func_id.name ^ ")" +end + +(* function hashtable definition *) +module FuncTable = Hashtbl.Make(Id) + + +module rec Info : sig + type functions = Id.t list + type info = { + params : string list; + nested : functions; + } + + type t = { + top_lvl : functions ref; + functions : info FuncTable.t; + } + + (* ---- primitive functions ----- *) + val empty : t + val find : t -> Id.t -> info + val create : int -> t + val iter : (Id.t -> info -> unit) -> t -> unit + val add : t -> Id.t -> Id.t option -> string list -> unit + val get_func_id : t -> string -> Id.t option -> Id.t option + + + +end = struct + type functions = Id.t list + type info = { + params : string list; + nested : functions; + } + + type t = { + top_lvl : functions ref; + functions : info FuncTable.t; + } + + let empty = {top_lvl = ref []; functions = FuncTable.create 1} + let create (size : int) : t = { top_lvl = ref []; functions = FuncTable.create size } + let find (info : t) : Id.t -> info = FuncTable.find info.functions + let replace (info : t) : Id.t -> info -> unit = FuncTable.replace info.functions + let remove (info : t) (func_id : Id.t) : unit = + let top_lvl = info.top_lvl in + + top_lvl := List.filter (not << Id.equal func_id) !top_lvl; + FuncTable.remove info.functions func_id; + FuncTable.filter_map_inplace (fun _ info -> + Some {info with nested = List.filter (not << Id.equal func_id) info.nested} + ) info.functions + + let iter (f : Id.t -> info -> unit) (info : t) : unit = FuncTable.iter f info.functions + + + let get_top_lvl (info : t) : functions = !(info.top_lvl) + let add_top_lvl (info : t) (func : Id.t) : unit = + (info.top_lvl) := func :: !(info.top_lvl) + + let get_func_id (info : t) (func_name : string) (parent_id : Id.t option) : Id.t option = + let context = match parent_id with + | Some parent_id -> + let parent_info = find info parent_id in + parent_info.nested + | None -> get_top_lvl info + in + List.find_opt (((=) func_name) << Id.get_name) context + + + let add_nested (info : t) (parent_id : Id.t option) (func_id : Id.t) : unit = + match parent_id with + (* no parent node, add function to the top-level functions list *) + | None -> add_top_lvl info func_id + (* there is a parent node to add to its nested children*) + | Some key -> + let func_info = find info key in + replace info key {func_info with nested = func_id :: func_info.nested} + + let add (info : t) (func_id : Id.t) (parent_id : Id.t option) (params' : string list) : unit = + (* remove previous version if it exists *) + let prev_definition = get_func_id info (Id.get_name func_id) parent_id in + option_may (remove info) prev_definition; + + (* add found node information *) + let func_info : info = { + params = params'; + nested = []; + } in + replace info func_id func_info; + + (* add found node information to its parent *) + add_nested info parent_id func_id + +end + +module Context = struct + type t = { + path : Id.t list; + functions : Info.t + } + + let empty = {path = []; functions = Info.empty} + let create (functions' : Info.t) : t = { path = []; functions = functions'} + let visit (context : t) (id : Id.t) : t = {context with path = id :: context.path} + + let get_func_id (context : t) (func_name : string) : Id.t = + let get_func_info_id = Info.get_func_id context.functions in + let rec aux (path : Id.t list) : Id.t = + let parent_id = hd_opt path in + let id = get_func_info_id func_name parent_id in + + if Option.is_some id then Option.get id (* found function nested inside parent id *) + else if Option.is_some parent_id then aux (List.tl path) (* function not found yet but there is more parents to search *) + else failwith "function not found" (* function name wasnt found in any parent's nested list *) + + in + aux context.path + + let get_func_info (context : t) (func_name : string) : Info.info = + let func_id = get_func_id context func_name in + Info.find context.functions func_id + + let get_param_names (context : t) (func_name : string) : string list = + let func_info = get_func_info context func_name in + func_info.params + + let is_last_definition (context : t) (id : Id.t) : bool = + let get_func_info_id = Info.get_func_id context.functions in + let parent_id = hd_opt context.path in + let found_id = get_func_info_id id.name parent_id in + + map_default_lazy + (fun found_id -> (Id.get_id found_id) = (Id.get_id id)) + (lazy (failwith ("function " ^ id.name ^ " is not definied in the given context"))) found_id + +end + + + +(* module rec Info : sig + type info = { + params : string list; + context : FuncTable.Id.t list; + } + + type t = info FuncTable.t + + (* ---- primitive functions ----- *) + val create : int -> t + val add : t -> string -> int -> string list -> t + val iter : (string -> info -> unit) -> t -> unit + + val get_info : t list -> string -> info + val get_param_name : t list -> string -> int -> string + +end = struct + type info = { + id : int; + params : string list; + context : Info.t; + } + + type t = info HashTable.t + + (* ------- S T R U C T U R E F U N C T I O N S ------- *) + let create = HashTable.create + let find_opt : t -> string -> info option = HashTable.find_opt + + let add (info : t) (func : string) (id' : int) (params' : string list) : t = + let new_context = create 5 in + let func_info : info = { + id = id'; + params = params'; + context = new_context; + } in + + HashTable.replace info func func_info; + new_context + + let iter : (string -> info -> unit) -> t -> unit = HashTable.iter + + + (* ------- I N F O M A N I P U L A T I O N ------- *) + let rec get_info (functions : t list) (func_name : string) : info = + match functions with + | [] -> failwith "function not defined in the given context" + | context::rest -> + let info = find_opt context func_name in + if Option.is_some info + then Option.get info + else get_info rest func_name + + let get_param_name (functions : t list) (func_name : string) (index : int) : string = + let info = get_info functions func_name in + List.nth info.params index + +end *) \ No newline at end of file diff --git a/lib/ast/structures/grammar.ml b/lib/ast/structures/grammar.ml index 7353903..ac2d4ef 100644 --- a/lib/ast/structures/grammar.ml +++ b/lib/ast/structures/grammar.ml @@ -1,4 +1,3 @@ -open Auxiliary.Structures open Auxiliary.Functions module Ast' = Flow_ast @@ -14,9 +13,9 @@ module Location = struct _end : position; } - let empty : t = - let empty_position = {line = 0; column = 0} in - { _start = empty_position; _end = empty_position };; + let empty () : t = + let empty_position () : position = {line = 0; column = 0} in + { _start = empty_position (); _end = empty_position ()};; let rec convert_flow_loc ({start; _end; _} : Loc.t) : t = let start' = convert_flow_pos start in @@ -29,65 +28,6 @@ end type m = Location.t;; -module rec FunctionsInfo : sig - type info = { - id : int; - params : string list; - context : FunctionsInfo.t; - } - - type t = info HashTable.t - - (* ---- primitive functions ----- *) - val create : int -> t - val add : t -> string -> int -> string list -> t - val iter : (string -> info -> unit) -> t -> unit - - val get_info : t list -> string -> info - val get_param_name : t list -> string -> int -> string - -end = struct - type info = { - id : int; - params : string list; - context : FunctionsInfo.t; - } - - type t = info HashTable.t - - (* ------- S T R U C T U R E F U N C T I O N S ------- *) - let create = HashTable.create - let find_opt : t -> string -> info option = HashTable.find_opt - - let add (info : t) (func : string) (id' : int) (params' : string list) : t = - let new_context = create 5 in - let func_info : info = { - id = id'; - params = params'; - context = new_context; - } in - - HashTable.replace info func func_info; - new_context - - let iter : (string -> info -> unit) -> t -> unit = HashTable.iter - - - (* ------- I N F O M A N I P U L A T I O N ------- *) - let rec get_info (functions : t list) (func_name : string) : info = - match functions with - | [] -> failwith "function not defined in the given context" - | context::rest -> - let info = find_opt context func_name in - if Option.is_some info - then Option.get info - else get_info rest func_name - - let get_param_name (functions : t list) (func_name : string) (index : int) : string = - let info = get_info functions func_name in - List.nth info.params index - -end module Operator = struct module Assignment = struct @@ -1464,7 +1404,7 @@ end and Program : sig type 'M t' = { body : 'M Statement.t list; - functions : FunctionsInfo.t + functions : Functions.Info.t } type 'M t = 'M * 'M t' @@ -1473,54 +1413,55 @@ and Program : sig end = struct type 'M t' = { body : 'M Statement.t list; - functions : FunctionsInfo.t + functions : Functions.Info.t } type 'M t = 'M * 'M t' - let build_function_info (body : 'M Statement.t list) : FunctionsInfo.t = - let rec traverse_body (context : FunctionsInfo.t) (stmts : 'M Statement.t list) : unit = - List.iter (search_functions context) stmts + let build_function_info (body : 'M Statement.t list) : Functions.Info.t = + let rec traverse_body found_funcs parent_id body : unit = + List.iter (search_functions found_funcs parent_id) body - and search_functions (context : FunctionsInfo.t) (stmt : 'M Statement.t) : unit = - match stmt with + and search_functions found_funcs parent_id statement : unit = + match statement with | _, Statement.AssignFunction {id; left; params; body; _} -> (* add function information *) - let left' = Identifier.get_name left in + let func_id = Functions.Id.create id (Identifier.get_name left) in let params' = List.map (fun (_, {Statement.AssignFunction.Param.argument; _}) -> Identifier.get_name argument) params in - let new_context = FunctionsInfo.add context left' id params' in - traverse_body new_context body; + + Functions.Info.add found_funcs func_id parent_id params'; + traverse_body found_funcs (Some func_id) body; (* --------- traverse ast --------- *) | _, Statement.If {consequent; alternate; _} -> - traverse_body context consequent; - option_may (traverse_body context) alternate; + traverse_body found_funcs parent_id consequent; + option_may (traverse_body found_funcs parent_id) alternate; | _, Statement.Switch {cases; _} -> List.iter (fun (_, {Statement.Switch.Case.consequent; _}) -> - traverse_body context consequent; + traverse_body found_funcs parent_id consequent; ) cases - | _, Statement.While {body; _} -> traverse_body context body - | _, Statement.ForIn {body; _} -> traverse_body context body - | _, Statement.ForOf {body; _} -> traverse_body context body - | _, Statement.With {body;_ } -> traverse_body context body - | _, Statement.Labeled {body; _} -> traverse_body context body + | _, Statement.While {body; _} -> traverse_body found_funcs parent_id body + | _, Statement.ForIn {body; _} -> traverse_body found_funcs parent_id body + | _, Statement.ForOf {body; _} -> traverse_body found_funcs parent_id body + | _, Statement.With {body;_ } -> traverse_body found_funcs parent_id body + | _, Statement.Labeled {body; _} -> traverse_body found_funcs parent_id body | _, Statement.Try {body; handler; finalizer} -> - traverse_body context body; - option_may (fun (_, {Statement.Try.Catch.body; _}) -> traverse_body context body) handler; - option_may (traverse_body context) finalizer; + traverse_body found_funcs parent_id body; + option_may (fun (_, {Statement.Try.Catch.body; _}) -> traverse_body found_funcs parent_id body) handler; + option_may (traverse_body found_funcs parent_id) finalizer; (* ------- ignore all other statements ------- *) | _ -> () in - let funcs_info = FunctionsInfo.create 20 in - traverse_body funcs_info body; - funcs_info + let info = Functions.Info.create 20 in + traverse_body info None body; + info let build (metadata : 'M) (stmts : 'M Statement.t list) : 'M t = (metadata, { body = stmts; functions = build_function_info stmts});; diff --git a/lib/auxiliary/functions.ml b/lib/auxiliary/functions.ml index 959efa8..4f351a2 100644 --- a/lib/auxiliary/functions.ml +++ b/lib/auxiliary/functions.ml @@ -16,4 +16,9 @@ let map_default_lazy f x value = let option_may f x : unit = match x with | Some x -> f x - | None -> () \ No newline at end of file + | None -> () + +let hd_opt (lst : 'a list) : 'a option = + match lst with + | [] -> None + | fst::_ -> Some fst \ No newline at end of file diff --git a/lib/mdg/analyse.ml b/lib/mdg/analyse.ml index 6ff73b2..9bd6829 100644 --- a/lib/mdg/analyse.ml +++ b/lib/mdg/analyse.ml @@ -1,5 +1,6 @@ (* open Auxiliary.Functions *) module Graph = Graph' +module Functions = Ast.Functions open Ast.Grammar open Auxiliary.Functions open Structures @@ -37,28 +38,28 @@ and analyse (state : state) (statement : m Statement.t) : unit = let lookup = Graph.lookup graph in let new_version = Graph.staticNewVersion graph in let new_version' = Graph.dynamicNewVersion graph in - let get_info = FunctionsInfo.get_info contx in - let get_param_name = FunctionsInfo.get_param_name contx in + let get_param_locs = Graph.get_param_locations graph in + let get_param_names = Functions.Context.get_param_names contx in + let get_func_id = Functions.Context.get_func_id contx in + let is_last_definition = Functions.Context.is_last_definition contx in + let visit = Functions.Context.visit contx in - print_string (Ast.Pp.Js.print_stmt statement 0); - Store.print store; - print_endline "--------------"; (match statement with (* -------- A S S I G N - E X P R -------- *) | _, AssignSimple {left; right} -> let _L = eval_expr right in store_update left _L - | _, AssignFunction {id; left; body; _} -> - let func_name = Identifier.get_name left in - let info = get_info func_name in - if (info.id = id) then ( - let param_locs = Graph.get_param_locations graph func_name in - let new_store = Store.empty in - List.iteri (fun i loc -> Store.update' new_store (List.nth info.params i) (LocationSet.singleton loc)) param_locs; - let new_state = {state with store = new_store; context = info.context :: contx} in + | _, AssignFunction {left; id; body; _} -> + let func_id : Functions.Id.t = {uid = id; name = Identifier.get_name left} in + (* functions with the same name can be nested inside the same context + (only consider the last definition with such name) *) + if is_last_definition func_id then + (* setup new store with only the param and corresponding locations *) + let param_locs = get_param_locs func_id in + let new_state = {state with store = param_locs; context = visit func_id} in analyse_sequence new_state body; - ); + (* -------- A S S I G N - O P -------- *) | _, AssignBinary {left; opLeft; opRght; id; _} -> @@ -125,17 +126,19 @@ and analyse (state : state) (statement : m Statement.t) : unit = (* -------- C A L L -------- *) - | _, AssignNewCall {left; callee=(_, {name=f; _}); arguments; id_call; id_retn; _} - | _, AssignFunCall {left; callee=(_, {name=f; _}); arguments; id_call; id_retn; _} -> + | _, AssignNewCall {left; callee; arguments; id_call; id_retn; _} + | _, AssignFunCall {left; callee; arguments; id_call; id_retn; _} -> + let f = Identifier.get_name callee in let _Lss = List.map eval_expr arguments in let l_call = alloc id_call in (* argument edges *) + let params = get_param_names f in List.iteri ( fun i _Ls -> - LocationSet.iter (fun l -> add_arg_edge l l_call (get_param_name f i)) _Ls + LocationSet.iter (fun l -> add_arg_edge l l_call (List.nth params i)) _Ls ) _Lss; (* call edge *) - let l_f = Graph.get_func_node graph f in + let l_f = Graph.get_func_node graph (get_func_id f) in add_call_edge l_call (Option.get l_f); add_node l_call (f ^ "()"); @@ -243,37 +246,26 @@ and property_lookup_name (left : m Identifier.t) (_object : m Expression.t) (pro let obj_prop = Expression.get_id _object ^ "." ^ property in if Identifier.is_generated left then obj_prop else Identifier.get_name left ^ ", " ^ obj_prop -and initialize_functions (state : state) (funcs_info : FunctionsInfo.t) : state = - let rec initialize_functions' (state : state) (to_process : FunctionsInfo.t list) : unit = - match to_process with - | [] -> () - | context::rest -> - let to_process = ref rest in - FunctionsInfo.iter (fun func info -> - initilize_function' state func info; - to_process := info.context :: !to_process; - ) context; - initialize_functions' state !to_process - - and initilize_function' (state : state) (func_name : string) (info : FunctionsInfo.info) : unit = - let graph = state.graph in - - let l_f = Graph.alloc_function graph in - Graph.add_func_node graph l_f func_name; - - (* add this param node and edge*) - let l_p = Graph.alloc_param graph in +and initialize_functions (state : state) (funcs_info : Functions.Info.t) : state = + let init_func_header (state : state) (func : Functions.Id.t) (info : Functions.Info.info) : unit = + let graph = state.graph in + let alloc_fun = Graph.alloc_function graph in + let add_fun_node = Graph.add_func_node graph in + let add_par_node = Graph.add_param_node graph in + let add_par_edge = Graph.add_param_edge graph in - Graph.add_param_node graph l_p "this"; - Graph.add_param_edge graph l_f l_p "this"; + let l_f = alloc_fun func.uid in + add_fun_node l_f func; (* add param nodes and edges *) List.iteri (fun i param -> let l_p = Graph.alloc_param graph in - Graph.add_param_node graph l_p param; - Graph.add_param_edge graph l_f l_p (Int.to_string i) - ) info.params; + add_par_node l_p param; + if param = "this" + then add_par_edge l_f l_p "this" + else add_par_edge l_f l_p (Int.to_string (i - 1)) + ) ("this" :: info.params); in - initialize_functions' state [funcs_info]; - {state with context = [funcs_info] } \ No newline at end of file + Functions.Info.iter (init_func_header state) funcs_info; + {state with context = Functions.Context.create funcs_info } \ No newline at end of file diff --git a/lib/mdg/structures/graph'.ml b/lib/mdg/structures/graph'.ml index 719e894..d7ed176 100644 --- a/lib/mdg/structures/graph'.ml +++ b/lib/mdg/structures/graph'.ml @@ -1,3 +1,4 @@ +module Functions = Ast.Functions open Structures open Auxiliary.Functions open Auxiliary.Structures @@ -7,18 +8,18 @@ open Ast.Grammar module Node = struct type t = | Object of string - | Function of string + | Function of Functions.Id.t | Parameter of string - let equals (node : t) (node' : t) = match (node, node') with + let equal (node : t) (node' : t) = match (node, node') with | Object x, Object x' - | Function x, Function x' | Parameter x, Parameter x' -> String.equal x x' + | Function x, Function x' -> Functions.Id.equal x x' | _ -> false let label (node : t) = match node with | Object obj -> obj - | Function func -> func + | Function func -> func.name | Parameter param -> param end @@ -123,10 +124,11 @@ let iter_nodes (f : location -> Node.t -> unit) (graph : t) = HashTable.iter f g let find_node_opt' : Node.t HashTable.t -> location -> Node.t option = HashTable.find_opt let find_node_opt (graph : t) : location -> Node.t option = find_node_opt' graph.nodes +let find_node (graph : t) : location -> Node.t = HashTable.find graph.nodes let replace_node (graph : t) (location : location) (node : Node.t) = let old_node = find_node_opt graph location in - map_default_lazy (fun old_node -> if not (Node.equals old_node node) then (graph.register ()) ) (lazy (graph.register ())) old_node; + map_default_lazy (fun old_node -> if not (Node.equal old_node node) then (graph.register ()) ) (lazy (graph.register ())) old_node; HashTable.replace graph.nodes location node (* > GRAPH FUNCTIONS : *) @@ -163,10 +165,10 @@ let get_property (graph : t) (location : location) (property : property option) let edges = get_edges graph location in Edge.get_to (EdgeSet.find_pred (is_property_edge property) edges) -let get_params (graph : t) (location : location) : location list = +let get_params (graph : t) (location : location) : EdgeSet.t = let edges = get_edges graph location in let params = EdgeSet.filter (Edge.is_param) edges in - EdgeSet.map_list (Edge.get_to) params + params (* ------- M A I N F U N C T I O N S -------*) let lub (graph : t) (graph' : t) : unit = @@ -176,9 +178,10 @@ let lub (graph : t) (graph' : t) : unit = replace_edges graph from (EdgeSet.union edges edges'); (* also update node info *) - if Option.is_none node' then - let node = find_node_opt graph from in - option_may (replace_node graph from) node + let node = find_node_opt graph from in + if Option.is_none node then + option_may (replace_node graph from) node' + ) graph' let alloc (_ : t) (id : int) : location = @@ -192,13 +195,8 @@ let alloc_param : t -> location = in alloc -let alloc_function : t -> location = - let id : int ref = ref 0 in - let alloc (_ : t) : location = - id := !id + 1; - loc_fun_prefix ^ (string_of_int !id) - in - alloc +let alloc_function (_ : t) (id : int) : location = + loc_fun_prefix ^ (Int.to_string id) let orig (graph : t) (l : location) : LocationSet.t = @@ -278,8 +276,8 @@ let add_obj_node (graph : t) (loc : location) (name : string) : unit = let node : Node.t = Object name in add_node graph loc node -let add_func_node (graph : t) (loc : location) (func_name) : unit = - let node : Node.t = Function func_name in +let add_func_node (graph : t) (loc : location) (func_id : Functions.Id.t) : unit = + let node : Node.t = Function func_id in add_node graph loc node let add_param_node (graph : t) (loc : location) (param : string) : unit = @@ -319,19 +317,27 @@ let add_ret_edge (graph : t) (from : location) (_to : location) : unit = let edge = {Edge._to = _to; _type = Return} in add_edge graph edge _to from -let get_func_node (graph : t) (func_name : string) : location option = +let get_func_node (graph : t) (func_id : Functions.Id.t) : location option = let res : location option ref = ref None in iter_nodes ( fun location node -> match node with - | Function func_name' -> if func_name = func_name' then res := Some location + | Function func_id' -> if Functions.Id.equal func_id func_id' then res := Some location | _ -> () ) graph; !res -let get_param_locations (graph : t) (func_name : string) : location list = - let func_loc = get_func_node graph func_name in - (* remove this from the parameter list *) - List.tl (get_params graph (Option.get func_loc)) +let get_param_locations (graph : t) (func_id : Functions.Id.t) : Store.t = + let func_loc = get_func_node graph func_id in + let params = get_params graph (Option.get func_loc) in + + let store = Store.empty () in + EdgeSet.iter (fun edge -> + let location = Edge.get_to edge in + let param_name = Node.label (find_node graph location) in + Store.update' store param_name (LocationSet.singleton location) + ) params; + + store let staticAddProperty (graph : t) (_L : LocationSet.t) (property : property) (id : int) (name : string) : unit = diff --git a/lib/mdg/structures/state.ml b/lib/mdg/structures/state.ml index 05e89c1..3a3c24f 100644 --- a/lib/mdg/structures/state.ml +++ b/lib/mdg/structures/state.ml @@ -1,5 +1,5 @@ open Structures -open Ast.Grammar +module Functions = Ast.Functions module Graph = Graph' let register, setup, was_changed = @@ -22,15 +22,15 @@ type state = { store : Store.t; this : LocationSet.t; (* function information *) - context : FunctionsInfo.t list; + context : Functions.Context.t; } let empty_state = { graph = Graph.empty register; - store = Store.empty; + store = Store.empty (); this = Store.this_loc; (* function information *) - context = []; + context = Functions.Context.empty; } let copy ({graph; store; _} as state : state) : state = diff --git a/lib/mdg/structures/store.ml b/lib/mdg/structures/store.ml index 1afada5..b506783 100644 --- a/lib/mdg/structures/store.ml +++ b/lib/mdg/structures/store.ml @@ -7,7 +7,7 @@ open Auxiliary.Functions type t = LocationSet.t HashTable.t -let empty : t = HashTable.create 100 +let empty () : t = HashTable.create 100 let literal_loc = LocationSet.singleton (loc_obj_prefix ^ "literal") let this_loc = LocationSet.singleton "this"