diff options
-rw-r--r-- | otherlibs/labltk/browser/searchpos.ml | 10 | ||||
-rw-r--r-- | otherlibs/labltk/browser/shell.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/lexer.mll | 2 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/maincompile.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/tables.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/jpf/balloon.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/fileevent.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/protocol.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/textvariable.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/widget.ml | 2 | ||||
-rw-r--r-- | stdlib/buffer.mli | 2 | ||||
-rw-r--r-- | stdlib/hashtbl.mli | 4 |
12 files changed, 21 insertions, 21 deletions
diff --git a/otherlibs/labltk/browser/searchpos.ml b/otherlibs/labltk/browser/searchpos.ml index 59d61407a..5aa58e814 100644 --- a/otherlibs/labltk/browser/searchpos.ml +++ b/otherlibs/labltk/browser/searchpos.ml @@ -67,8 +67,8 @@ let rec list_of_path = function (* a simple wrapper *) -class buffer :len = object - val buffer = Buffer.create len +class buffer :size = object + val buffer = Buffer.create :size method out :buf = Buffer.add_substring buffer buf method get = Buffer.contents buffer end @@ -225,7 +225,7 @@ type module_widgets = mw_edit: Widget.button Widget.widget; mw_intf: Widget.button Widget.widget } -let shown_modules = Hashtbl.create 17 +let shown_modules = Hashtbl.create size:17 let filter_modules () = Hashtbl.iter shown_modules fun: begin fun :key :data -> @@ -457,7 +457,7 @@ and view_decl_menu lid :kind :env :parent = command:(fun () -> view_decl lid :kind :env); end; if kind = `Type or kind = `Modtype then begin - let buf = new buffer len:60 in + let buf = new buffer size:60 in let (fo,ff) = Format.get_formatter_output_functions () and margin = Format.get_margin () in Format.set_formatter_output_functions out:buf#out flush:(fun () -> ()); @@ -552,7 +552,7 @@ let view_type_menu kind :env :parent = end; begin match kind with `Module _ | `Class _ -> () | `Exp(_, ty) -> - let buf = new buffer len:60 in + let buf = new buffer size:60 in let (fo,ff) = Format.get_formatter_output_functions () and margin = Format.get_margin () in Format.set_formatter_output_functions out:buf#out flush:(fun () -> ()); diff --git a/otherlibs/labltk/browser/shell.ml b/otherlibs/labltk/browser/shell.ml index f63388754..88492cc9e 100644 --- a/otherlibs/labltk/browser/shell.ml +++ b/otherlibs/labltk/browser/shell.ml @@ -44,7 +44,7 @@ let dump_mem ?(:pos = 0) ?:len obj = match len with | None -> Obj.size obj * Sys.word_size / 8 - pos | Some x -> x in - let buf = Buffer.create 256 in + let buf = Buffer.create size:256 in for i = pos to len - 1 do let c = String.unsafe_get (Obj.obj obj) i in Buffer.add_string buf (Printf.sprintf "%02x" (Char.code c)) @@ -74,7 +74,7 @@ object (self) val h = new history () val mutable alive = true val mutable reading = false - val ibuffer = Buffer.create 1024 + val ibuffer = Buffer.create size:1024 val imutex = Mutex.create () val mutable ithreads = [] method alive = alive 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 *) diff --git a/otherlibs/labltk/jpf/balloon.ml b/otherlibs/labltk/jpf/balloon.ml index b571e0c52..c783a0be6 100644 --- a/otherlibs/labltk/jpf/balloon.ml +++ b/otherlibs/labltk/jpf/balloon.ml @@ -77,7 +77,7 @@ let put on: w ms: millisec mesg = end let init () = - let t = Hashtbl.create 101 in + let t = Hashtbl.create size:101 in Protocol.add_destroy_hook (fun w -> Hashtbl.remove t key:w); topw := Toplevel.create default_toplevel; diff --git a/otherlibs/labltk/support/fileevent.ml b/otherlibs/labltk/support/fileevent.ml index 4dac902bf..3fd4243dd 100644 --- a/otherlibs/labltk/support/fileevent.ml +++ b/otherlibs/labltk/support/fileevent.ml @@ -29,7 +29,7 @@ external rem_file_output : file_descr -> unit (* File input handlers *) -let fd_table = Hashtbl.create 37 (* Avoid space leak in callback table *) +let fd_table = Hashtbl.create size:37 (* Avoid space leak in callback table *) let add_fileinput :fd callback:f = let id = new_function_id () in diff --git a/otherlibs/labltk/support/protocol.ml b/otherlibs/labltk/support/protocol.ml index 522eab8c1..9d7cb2e1f 100644 --- a/otherlibs/labltk/support/protocol.ml +++ b/otherlibs/labltk/support/protocol.ml @@ -92,10 +92,10 @@ let cTKtoCAMLwidget = function let callback_naming_table = - (Hashtbl.create 401 : (int, callback_buffer -> unit) Hashtbl.t) + (Hashtbl.create size:401 : (int, callback_buffer -> unit) Hashtbl.t) let callback_memo_table = - (Hashtbl.create 401 : (any widget, int) Hashtbl.t) + (Hashtbl.create size:401 : (any widget, int) Hashtbl.t) let new_function_id = let counter = ref 0 in diff --git a/otherlibs/labltk/support/textvariable.ml b/otherlibs/labltk/support/textvariable.ml index f467a7150..adeb85032 100644 --- a/otherlibs/labltk/support/textvariable.ml +++ b/otherlibs/labltk/support/textvariable.ml @@ -28,7 +28,7 @@ external get : string -> string = "camltk_getvar" type textVariable = string (* List of handles *) -let handles = Hashtbl.create 401 +let handles = Hashtbl.create size:401 let add_handle var cbid = try @@ -85,7 +85,7 @@ let handle vname f = module StringSet = Set.Make(struct type t = string let compare = compare end) let freelist = ref (StringSet.empty) -let memo = Hashtbl.create 101 +let memo = Hashtbl.create size:101 (* Added a variable v referenced by widget w *) let add w v = diff --git a/otherlibs/labltk/support/widget.ml b/otherlibs/labltk/support/widget.ml index 2174fc3cb..883d8624f 100644 --- a/otherlibs/labltk/support/widget.ml +++ b/otherlibs/labltk/support/widget.ml @@ -50,7 +50,7 @@ let forget_type w = (Obj.magic (w : 'a widget) : any widget) let coe = forget_type (* table of widgets *) -let table = (Hashtbl.create 401 : (string, any widget) Hashtbl.t) +let table = (Hashtbl.create size:401 : (string, any widget) Hashtbl.t) let name = function Untyped s -> s diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index 1f9728d94..1a2866704 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -20,7 +20,7 @@ type t (* The abstract type of buffers. *) -val create : int -> t +val create : size:int -> t (* [create n] returns a fresh buffer, initially empty. The [n] parameter is the initial size of the internal string that holds the buffer contents. That string is automatically diff --git a/stdlib/hashtbl.mli b/stdlib/hashtbl.mli index ad8e6b9e1..9364edac9 100644 --- a/stdlib/hashtbl.mli +++ b/stdlib/hashtbl.mli @@ -21,7 +21,7 @@ type ('a, 'b) t (* The type of hash tables from type ['a] to type ['b]. *) -val create : int -> ('a,'b) t +val create : size:int -> ('a,'b) t (* [Hashtbl.create n] creates a new, empty hash table, with initial size [n]. For best results, [n] should be on the order of the expected number of elements that will be in @@ -88,7 +88,7 @@ module type S = sig type key type 'a t - val create: int -> 'a t + val create: size:int -> 'a t val clear: 'a t -> unit val add: 'a t -> key:key -> data:'a -> unit val remove: 'a t -> key:key -> unit |