Skip to content

Commit

Permalink
PR#5677: do not use "value" as identifier (genprintval.ml)
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12690 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
Damien Doligez committed Jul 10, 2012
1 parent 9c3b2b4 commit 1330131
Show file tree
Hide file tree
Showing 5 changed files with 11 additions and 10 deletions.
1 change: 1 addition & 0 deletions Changes
Expand Up @@ -169,6 +169,7 @@ Bug Fixes:
- PR#5655: ocamlbuild doesn't pass cflags when building C stubs
- PR#5661: fixes for the test suite
- PR#5671: initialization of compare_ext field in caml_final_custom_operations()
- PR#5677: do not use "value" as identifier (genprintval.ml)
- problem with printing of string literals in camlp4 (reported on caml-list)
- emacs mode: colorization of comments and strings now works correctly

Expand Down
2 changes: 1 addition & 1 deletion debugger/printval.ml
Expand Up @@ -47,7 +47,7 @@ let check_depth ppf depth obj ty =

module EvalPath =
struct
type value = Debugcom.Remote_value.t
type valu = Debugcom.Remote_value.t
exception Error
let rec eval_path = function
Pident id ->
Expand Down
8 changes: 4 additions & 4 deletions toplevel/genprintval.ml
Expand Up @@ -33,10 +33,10 @@ module type OBJ =

module type EVALPATH =
sig
type value
val eval_path: Path.t -> value
type valu
val eval_path: Path.t -> valu
exception Error
val same_value: value -> value -> bool
val same_value: valu -> valu -> bool
end

module type S =
Expand All @@ -52,7 +52,7 @@ module type S =
Env.t -> t -> type_expr -> Outcometree.out_value
end

module Make(O : OBJ)(EVP : EVALPATH with type value = O.t) = struct
module Make(O : OBJ)(EVP : EVALPATH with type valu = O.t) = struct

type t = O.t

Expand Down
8 changes: 4 additions & 4 deletions toplevel/genprintval.mli
Expand Up @@ -29,10 +29,10 @@ module type OBJ =

module type EVALPATH =
sig
type value
val eval_path: Path.t -> value
type valu
val eval_path: Path.t -> valu
exception Error
val same_value: value -> value -> bool
val same_value: valu -> valu -> bool
end

module type S =
Expand All @@ -48,5 +48,5 @@ module type S =
Env.t -> t -> type_expr -> Outcometree.out_value
end

module Make(O : OBJ)(EVP : EVALPATH with type value = O.t) :
module Make(O : OBJ)(EVP : EVALPATH with type valu = O.t) :
(S with type t = O.t)
2 changes: 1 addition & 1 deletion toplevel/toploop.ml
Expand Up @@ -65,7 +65,7 @@ let rec eval_path = function
(* To print values *)

module EvalPath = struct
type value = Obj.t
type valu = Obj.t
exception Error
let eval_path p = try eval_path p with Symtable.Error _ -> raise Error
let same_value v1 v2 = (v1 == v2)
Expand Down

0 comments on commit 1330131

Please sign in to comment.