summaryrefslogtreecommitdiffstats
path: root/otherlibs/labltk/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/labltk/compiler')
-rw-r--r--otherlibs/labltk/compiler/lexer.mll2
-rw-r--r--otherlibs/labltk/compiler/maincompile.ml2
-rw-r--r--otherlibs/labltk/compiler/tables.ml4
3 files changed, 4 insertions, 4 deletions
diff --git a/otherlibs/labltk/compiler/lexer.mll b/otherlibs/labltk/compiler/lexer.mll
index 92ff0921d..a2251b902 100644
--- a/otherlibs/labltk/compiler/lexer.mll
+++ b/otherlibs/labltk/compiler/lexer.mll
@@ -25,7 +25,7 @@ let current_line = ref 1
(* The table of keywords *)
-let keyword_table = (Hashtbl.create 149 : (string, token) Hashtbl.t)
+let keyword_table = (Hashtbl.create size:149 : (string, token) Hashtbl.t)
let _ = List.iter
fun:(fun (str,tok) -> Hashtbl.add keyword_table key:str data:tok)
diff --git a/otherlibs/labltk/compiler/maincompile.ml b/otherlibs/labltk/compiler/maincompile.ml
index ebbf420ae..fd6c7ddc4 100644
--- a/otherlibs/labltk/compiler/maincompile.ml
+++ b/otherlibs/labltk/compiler/maincompile.ml
@@ -111,7 +111,7 @@ let uniq_clauses = function
prerr_endline err;
fatal_error err
end in
- let t = Hashtbl.create 11 in
+ let t = Hashtbl.create size:11 in
List.iter l
fun:(fun constr ->
let c = constr.var_name in
diff --git a/otherlibs/labltk/compiler/tables.ml b/otherlibs/labltk/compiler/tables.ml
index 29c2588ff..41602b2bf 100644
--- a/otherlibs/labltk/compiler/tables.ml
+++ b/otherlibs/labltk/compiler/tables.ml
@@ -99,7 +99,7 @@ type module_def = {
(******************** The tables ********************)
(* the table of all explicitly defined types *)
-let types_table = (Hashtbl.create 37 : (string, type_def) Hashtbl.t)
+let types_table = (Hashtbl.create size:37 : (string, type_def) Hashtbl.t)
(* "builtin" types *)
let types_external = ref ([] : (string * parser_arity) list)
(* dependancy order *)
@@ -109,7 +109,7 @@ let types_returned = ref ([] : string list)
(* Function table *)
let function_table = ref ([] : fullcomponent list)
(* Widget/Module table *)
-let module_table = (Hashtbl.create 37 : (string, module_def) Hashtbl.t)
+let module_table = (Hashtbl.create size:37 : (string, module_def) Hashtbl.t)
(* variant name *)