transl_exception_constructor now uses Immutable

master
Mark Shinwell 2015-10-28 10:56:49 +00:00
parent 4bd9adbdc7
commit 17e1078cce
5 changed files with 11 additions and 6 deletions

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -45,8 +45,8 @@ let field_path path field =
(* Compile type extensions *)
let prim_set_oo_id =
Pccall (Primitive.simple ~name:"caml_set_oo_id" ~arity:1 ~alloc:false)
let prim_fresh_oo_id =
Pccall (Primitive.simple ~name:"caml_fresh_oo_id" ~arity:1 ~alloc:false)
let transl_extension_constructor env path ext =
let name =
@ -56,10 +56,9 @@ let transl_extension_constructor env path ext =
in
match ext.ext_kind with
Text_decl(args, ret) ->
Lprim(prim_set_oo_id,
[Lprim(Pmakeblock(Obj.object_tag, Mutable),
[Lconst(Const_base(Const_string (name,None)));
Lconst(Const_base(Const_int 0))])])
Lprim (Pmakeblock (Obj.object_tag, Immutable),
[Lconst (Const_base (Const_string (name, None)));
Lprim (prim_fresh_oo_id, [Lconst (Const_base (Const_int 0))])])
| Text_rebind(path, lid) ->
transl_path ~loc:ext.ext_loc env path

View File

@ -245,6 +245,12 @@ CAMLprim value caml_set_oo_id (value obj) {
return obj;
}
CAMLprim value caml_fresh_oo_id (value v) {
v = oo_last_id;
oo_last_id += 2;
return v;
}
CAMLprim value caml_int_as_pointer (value n) {
return n - 1;
}