summaryrefslogtreecommitdiffstats
path: root/stdlib/weak.ml
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2014-08-22 13:45:02 +0000
committerDamien Doligez <damien.doligez-inria.fr>2014-08-22 13:45:02 +0000
commitcbfe627f925ab2bab93bae7a7bc9f6ee6afb8637 (patch)
treeaf5ec283ac3175b1ab95dd745dbd05f2298b9da6 /stdlib/weak.ml
parent09ad9c1abbe6bee443a55379223280dab3de4749 (diff)
merge changes from branch 4.02 from branching (rev 14852) to 4.02.0+rc1 (rev 15121)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15125 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/weak.ml')
-rw-r--r--stdlib/weak.ml4
1 files changed, 2 insertions, 2 deletions
diff --git a/stdlib/weak.ml b/stdlib/weak.ml
index 536a42e04..8166142b6 100644
--- a/stdlib/weak.ml
+++ b/stdlib/weak.ml
@@ -80,8 +80,8 @@ module Make (H : Hashtbl.HashedType) : (S with type data = H.t) = struct
let sz = if sz < 7 then 7 else sz in
let sz = if sz > Sys.max_array_length then Sys.max_array_length else sz in
{
- table = Array.create sz emptybucket;
- hashes = Array.create sz [| |];
+ table = Array.make sz emptybucket;
+ hashes = Array.make sz [| |];
limit = limit;
oversize = 0;
rover = 0;