summaryrefslogtreecommitdiffstats
path: root/stdlib/camlinternalMod.ml
diff options
context:
space:
mode:
authorJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2014-03-10 02:54:02 +0000
committerJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2014-03-10 02:54:02 +0000
commit65b11934069a7b55d60fb68b09de8b397ad7e491 (patch)
treed4932b18f01b9d13d5af158f1f12276b0418258d /stdlib/camlinternalMod.ml
parentd59bd570d72d4a0c7a78a97e6a451a7851b255fe (diff)
Fix PR#6307
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14451 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/camlinternalMod.ml')
-rw-r--r--stdlib/camlinternalMod.ml5
1 files changed, 5 insertions, 0 deletions
diff --git a/stdlib/camlinternalMod.ml b/stdlib/camlinternalMod.ml
index 20a65207f..5f1882a2b 100644
--- a/stdlib/camlinternalMod.ml
+++ b/stdlib/camlinternalMod.ml
@@ -16,6 +16,7 @@ type shape =
| Lazy
| Class
| Module of shape array
+ | Value of Obj.t
let rec init_mod loc shape =
match shape with
@@ -32,6 +33,8 @@ let rec init_mod loc shape =
Obj.repr (CamlinternalOO.dummy_class loc)
| Module comps ->
Obj.repr (Array.map (init_mod loc) comps)
+ | Value v ->
+ v
let overwrite o n =
assert (Obj.size o >= Obj.size n);
@@ -64,3 +67,5 @@ let rec update_mod shape o n =
for i = 0 to Array.length comps - 1 do
update_mod comps.(i) (Obj.field o i) (Obj.field n i)
done
+ | Value v ->
+ overwrite o n