Skip to content

Commit

Permalink
big bug in Obj.add_offset
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/version/3.11@9559 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
doligez committed Jan 25, 2010
1 parent 4460021 commit 3550f37
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 6 deletions.
2 changes: 1 addition & 1 deletion byterun/obj.c
Expand Up @@ -167,7 +167,7 @@ CAMLprim value caml_obj_truncate (value v, value newsize)

CAMLprim value caml_obj_add_offset (value v, value offset)
{
return v + Int32_val (offset);
return v + (unsigned long) Int32_val (offset);
}

/* The following functions are used in stdlib/lazy.ml.
Expand Down
6 changes: 3 additions & 3 deletions stdlib/.depend
Expand Up @@ -24,7 +24,7 @@ map.cmi:
marshal.cmi:
moreLabels.cmi: set.cmi map.cmi hashtbl.cmi
nativeint.cmi:
obj.cmi:
obj.cmi: int32.cmi
oo.cmi: camlinternalOO.cmi
parsing.cmi: obj.cmi lexing.cmi
pervasives.cmi:
Expand Down Expand Up @@ -98,8 +98,8 @@ moreLabels.cmo: set.cmi map.cmi hashtbl.cmi moreLabels.cmi
moreLabels.cmx: set.cmx map.cmx hashtbl.cmx moreLabels.cmi
nativeint.cmo: sys.cmi pervasives.cmi nativeint.cmi
nativeint.cmx: sys.cmx pervasives.cmx nativeint.cmi
obj.cmo: marshal.cmi array.cmi obj.cmi
obj.cmx: marshal.cmx array.cmx obj.cmi
obj.cmo: marshal.cmi int32.cmi array.cmi obj.cmi
obj.cmx: marshal.cmx int32.cmx array.cmx obj.cmi
oo.cmo: camlinternalOO.cmi oo.cmi
oo.cmx: camlinternalOO.cmx oo.cmi
parsing.cmo: obj.cmi lexing.cmi array.cmi parsing.cmi
Expand Down
2 changes: 1 addition & 1 deletion stdlib/obj.ml
Expand Up @@ -32,7 +32,7 @@ let set_double_field x i v = Array.set (obj x : float array) i v
external new_block : int -> int -> t = "caml_obj_block"
external dup : t -> t = "caml_obj_dup"
external truncate : t -> int -> unit = "caml_obj_truncate"
external add_offset : t -> int -> t = "caml_obj_add_offset"
external add_offset : t -> Int32.t -> t = "caml_obj_add_offset"

let marshal (obj : t) =
Marshal.to_string obj []
Expand Down
2 changes: 1 addition & 1 deletion stdlib/obj.mli
Expand Up @@ -35,7 +35,7 @@ val set_double_field : t -> int -> float -> unit
external new_block : int -> int -> t = "caml_obj_block"
external dup : t -> t = "caml_obj_dup"
external truncate : t -> int -> unit = "caml_obj_truncate"
external add_offset : t -> int -> t = "caml_obj_add_offset"
external add_offset : t -> Int32.t -> t = "caml_obj_add_offset"

val lazy_tag : int
val closure_tag : int
Expand Down

0 comments on commit 3550f37

Please sign in to comment.