summaryrefslogtreecommitdiffstats
path: root/otherlibs/labltk/browser
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/labltk/browser')
-rw-r--r--otherlibs/labltk/browser/searchpos.ml10
-rw-r--r--otherlibs/labltk/browser/shell.ml4
2 files changed, 7 insertions, 7 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